diff --git a/app/GenerateTestCases.hs b/app/GenerateTestCases.hs
index eed1bfe9d..1e1bf71ef 100644
--- a/app/GenerateTestCases.hs
+++ b/app/GenerateTestCases.hs
@@ -142,7 +142,7 @@ runInitialCommitForSyntax metaRepo@JSONMetaRepo{..} metaSyntax@JSONMetaSyntax{..
Prelude.putStrLn $ "Generating initial commit for " <> syntax <> " syntax."
let repoFilePath' = repoFilePath metaRepo metaSyntax
-
+
result <- try . executeCommand (repoPath language) $ touchCommand repoFilePath' <> commitCommand syntax "Initial commit"
case ( result :: Either Prelude.IOError String) of
Left error -> Prelude.putStrLn $ "Initializing the " <> repoFilePath metaRepo metaSyntax <> " failed with: " <> show error <> ". " <> "Possible reason: file already initialized. \nProceeding to the next step."
@@ -192,14 +192,16 @@ runGenerateCommitAndTestCase opts JSONMetaRepo{..} testCaseFilePath (JSONMetaSyn
_ <- executeCommand (repoPath language) command
afterSha <- executeCommand (repoPath language) getLastCommitShaCommand
+ patch <- executeCommand (repoPath language) (gitDiffCommand beforeSha afterSha)
+
expectedResult' <- runExpectedResult (repoPath language) beforeSha afterSha (syntax <> fileExt) opts
let jsonTestCase = encodePretty JSONTestCase {
gitDir = extractGitDir (repoPath language),
testCaseDescription = language <> "-" <> syntax <> "-" <> description <> "-" <> "test",
filePaths = [syntax <> fileExt],
- sha1 = beforeSha,
- sha2 = afterSha,
+ shas = beforeSha <> ".." <> afterSha,
+ patch = lines patch,
expectedResult = expectedResult'
}
@@ -255,27 +257,37 @@ generateJSON args = do
let rows = fromMaybe (fromList [("rows", "")]) headResult ! "rows"
pure $ JSONResult ( Map.fromList [ ("oids", oids), ("paths", paths), ("rows", rows) ] )
--- | Commands represent the various combination of patches (insert, delete, replacement)
--- | for a given syntax.
-commands :: JSONMetaRepo -> JSONMetaSyntax -> [(JSONMetaSyntax, String, String, String)]
-commands metaRepo@JSONMetaRepo{..} metaSyntax@JSONMetaSyntax{..} =
- [ (metaSyntax, "insert", commaSeperator, fileAppendCommand repoFilePath' insert <> commitCommand syntax "insert")
- , (metaSyntax, "replacement-insert", commaSeperator, fileWriteCommand repoFilePath' templateText' <> fileAppendCommand repoFilePath' (Prologue.intercalate "\n" [replacement, insert, insert]) <> commitCommand syntax "replacement + insert + insert")
- , (metaSyntax, "delete-insert", commaSeperator, fileWriteCommand repoFilePath' templateText' <> fileAppendCommand repoFilePath' (Prologue.intercalate "\n" [insert, insert, insert]) <> commitCommand syntax "delete + insert")
- , (metaSyntax, "replacement", commaSeperator, fileWriteCommand repoFilePath' templateText' <> fileAppendCommand repoFilePath' (Prologue.intercalate "\n" [replacement, insert, insert]) <> commitCommand syntax "replacement")
- , (metaSyntax, "delete-replacement", commaSeperator, fileWriteCommand repoFilePath' templateText' <> fileAppendCommand repoFilePath' (Prologue.intercalate "\n" [insert, replacement]) <> commitCommand syntax "delete + replacement")
- , (metaSyntax, "delete", commaSeperator, fileWriteCommand repoFilePath' templateText' <> fileAppendCommand repoFilePath' replacement <> commitCommand syntax "delete")
- , (metaSyntax, "delete-rest", spaceSeperator, fileWriteCommand repoFilePath' templateText' <> commitCommand syntax "delete rest")
- ]
- where
- commaSeperator = "\n,"
- spaceSeperator = ""
- templateText' = fromMaybe "" templateText
- repoFilePath' = repoFilePath metaRepo metaSyntax
repoFilePath :: JSONMetaRepo -> JSONMetaSyntax -> String
repoFilePath metaRepo metaSyntax = syntax metaSyntax <> fileExt metaRepo
+-- | Commands represent the various combination of patches (insert, delete, replacement)
+-- | for a given syntax.
+commands :: JSONMetaRepo -> JSONMetaSyntax -> [(JSONMetaSyntax, String, String, String)]
+commands JSONMetaRepo{..} metaSyntax@JSONMetaSyntax{..} = case template of
+ (Just _) -> [ (metaSyntax, "setup", commaSeperator, fileWriteCommand repoFilePath (withTemplate "") <> commitCommand syntax "setup")
+ , (metaSyntax, "insert", commaSeperator, fileWriteCommand repoFilePath (withTemplate insert) <> commitCommand syntax "insert")
+ , (metaSyntax, "replacement", commaSeperator, fileWriteCommand repoFilePath (withTemplate replacement) <> commitCommand syntax "replacement")
+ , (metaSyntax, "delete-replacement", commaSeperator, fileWriteCommand repoFilePath (withTemplate insert) <> commitCommand syntax "delete replacement")
+ , (metaSyntax, "delete-insert", commaSeperator, fileWriteCommand repoFilePath (withTemplate "") <> commitCommand syntax "delete insert")
+ , (metaSyntax, "teardown", spaceSeperator, removeCommand repoFilePath <> touchCommand repoFilePath <> commitCommand syntax "teardown")
+ ]
+ Nothing -> [ (metaSyntax, "insert", commaSeperator, fileWriteCommand repoFilePath insert <> commitCommand syntax "insert")
+ , (metaSyntax, "replacement-insert", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [replacement, insert, insert]) <> commitCommand syntax "replacement + insert + insert")
+ , (metaSyntax, "delete-insert", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [insert, insert, insert]) <> commitCommand syntax "delete + insert")
+ , (metaSyntax, "replacement", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [replacement, insert, insert]) <> commitCommand syntax "replacement")
+ , (metaSyntax, "delete-replacement", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [insert, replacement]) <> commitCommand syntax "delete + replacement")
+ , (metaSyntax, "delete", commaSeperator, fileWriteCommand repoFilePath replacement <> commitCommand syntax "delete")
+ , (metaSyntax, "delete-rest", spaceSeperator, removeCommand repoFilePath <> touchCommand repoFilePath <> commitCommand syntax "delete rest")
+ ]
+ where commaSeperator = "\n,"
+ spaceSeperator = ""
+ repoFilePath = syntax <> fileExt
+ withTemplate = contentsWithTemplate template
+ contentsWithTemplate :: Maybe String -> String -> String
+ contentsWithTemplate (Just template) contents = DT.unpack $ DT.replace "{0}" (toS contents) (toS template)
+ contentsWithTemplate Nothing contents = contents
+
-- | Attempts to pull from the git repository's remote repository.
-- | If the pull fails, the exception is caught and continues to the next step.
runPullGitRemote :: String -> FilePath -> IO ()
@@ -321,6 +333,9 @@ addSubmoduleCommand repoUrl repoPath = "git submodule add " <> repoUrl <> " " <>
getLastCommitShaCommand :: String
getLastCommitShaCommand = "git log --pretty=format:\"%H\" -n 1;"
+gitDiffCommand :: String -> String -> String
+gitDiffCommand sha1 sha2 = "git diff " <> sha1 <> ".." <> sha2 <> ";"
+
checkoutMasterCommand :: String
checkoutMasterCommand = "git checkout master;"
diff --git a/semantic-diff.cabal b/semantic-diff.cabal
index b01e9c18c..78a8177ad 100644
--- a/semantic-diff.cabal
+++ b/semantic-diff.cabal
@@ -197,6 +197,7 @@ test-suite integration-test
, hspec >= 2.1.10
, hspec-expectations-pretty-diff
, semantic-diff
+ , split
, MissingH
, unordered-containers
ghc-options: -threaded -rtsopts -with-rtsopts=-N -j -pgml=script/g++
diff --git a/src/Category.hs b/src/Category.hs
index 0415a59a4..4c140c67a 100644
--- a/src/Category.hs
+++ b/src/Category.hs
@@ -128,6 +128,15 @@ data Category
| Until
-- | A unless/else expression.
| Unless
+ | Begin
+ | Else
+ | Elsif
+ | Ensure
+ | Rescue
+ | RescueModifier
+ | When
+ | RescuedException
+ | Negate
deriving (Eq, Generic, Ord, Show)
-- Instances
@@ -188,6 +197,15 @@ instance Arbitrary Category where
, pure Yield
, pure Until
, pure Unless
+ , pure Begin
+ , pure Else
+ , pure Elsif
+ , pure Ensure
+ , pure Rescue
+ , pure RescueModifier
+ , pure When
+ , pure RescuedException
+ , pure Negate
, Other <$> arbitrary
]
diff --git a/src/DiffSummary.hs b/src/DiffSummary.hs
index c24250f25..8ca102f2a 100644
--- a/src/DiffSummary.hs
+++ b/src/DiffSummary.hs
@@ -47,12 +47,19 @@ identifiable term = isIdentifiable (unwrap term) term
S.MathAssignment{} -> Identifiable
S.VarAssignment{} -> Identifiable
S.SubscriptAccess{} -> Identifiable
+ S.Module{} -> Identifiable
S.Class{} -> Identifiable
S.Method{} -> Identifiable
S.Leaf{} -> Identifiable
S.DoWhile{} -> Identifiable
S.Import{} -> Identifiable
S.Export{} -> Identifiable
+ S.Ternary{} -> Identifiable
+ S.If{} -> Identifiable
+ S.Try{} -> Identifiable
+ S.Switch{} -> Identifiable
+ S.Case{} -> Identifiable
+ S.Rescue{} -> Identifiable
_ -> Unidentifiable
data JSONSummary summary span = JSONSummary { summary :: summary, span :: span }
@@ -139,6 +146,10 @@ determiner :: DiffInfo -> Doc
determiner (LeafInfo "number" _ _) = ""
determiner (LeafInfo "integer" _ _) = ""
determiner (LeafInfo "boolean" _ _) = ""
+determiner (LeafInfo "begin statement" _ _) = "a"
+determiner (LeafInfo "else block" _ _) = "an"
+determiner (LeafInfo "ensure block" _ _) = "an"
+determiner (LeafInfo "when block" _ _) = "a"
determiner (LeafInfo "anonymous function" _ _) = "an"
determiner (BranchInfo bs _ _) = determiner (last bs)
determiner _ = "the"
@@ -152,6 +163,10 @@ toLeafInfos leaf = pure . flip JSONSummary (sourceSpan leaf) $ case leaf of
(LeafInfo "integer" termName _) -> squotes $ toDoc termName
(LeafInfo "boolean" termName _) -> squotes $ toDoc termName
(LeafInfo "anonymous function" termName _) -> toDoc termName <+> "function"
+ (LeafInfo cName@"begin statement" _ _) -> toDoc cName
+ (LeafInfo cName@"else block" _ _) -> toDoc cName
+ (LeafInfo cName@"ensure block" _ _) -> toDoc cName
+ (LeafInfo cName@"when block" _ _) -> toDoc cName
(LeafInfo cName@"string" termName _) -> toDoc termName <+> toDoc cName
(LeafInfo cName@"export statement" termName _) -> toDoc termName <+> toDoc cName
(LeafInfo cName@"import statement" termName _) -> toDoc termName <+> toDoc cName
@@ -192,12 +207,9 @@ toTermName source term = case unwrap term of
(_, _) -> toTermName' base <> "[" <> toTermName' element <> "]"
S.VarAssignment varId _ -> toTermName' varId
S.VarDecl decl -> toTermName' decl
- -- TODO: We should remove Args from Syntax since I don't think we should ever
- -- evaluate Args as a single toTermName Text - joshvera
- S.Args args -> mconcat $ toTermName' <$> args
-- TODO: We should remove Case from Syntax since I don't think we should ever
-- evaluate Case as a single toTermName Text - joshvera
- S.Case expr _ -> toTermName' expr
+ S.Case expr _ -> termNameFromSource expr
S.Switch expr _ -> toTermName' expr
S.Ternary expr _ -> toTermName' expr
S.MathAssignment id _ -> toTermName' id
@@ -213,10 +225,10 @@ toTermName source term = case unwrap term of
S.DoWhile _ expr -> toTermName' expr
S.Throw expr -> termNameFromSource expr
S.Constructor expr -> toTermName' expr
- S.Try expr _ _ -> termNameFromSource expr
+ S.Try clauses _ _ _ -> termNameFromChildren term clauses
S.Array _ -> termNameFromSource term
S.Class identifier _ _ -> toTermName' identifier
- S.Method identifier _ _ -> toTermName' identifier
+ S.Method identifier args _ -> toTermName' identifier <> paramsToArgNames args
S.Comment a -> toCategoryName a
S.Commented _ _ -> termNameFromChildren term (toList $ unwrap term)
S.Module identifier _ -> toTermName' identifier
@@ -226,8 +238,8 @@ toTermName source term = case unwrap term of
S.Export (Just identifier) [] -> "{ " <> toTermName' identifier <> " }"
S.Export (Just identifier) expr -> "{ " <> intercalate ", " (termNameFromSource <$> expr) <> " }" <> " from " <> toTermName' identifier
S.ConditionalAssignment id _ -> toTermName' id
- S.Until expr _ -> toTermName' expr
- S.Unless expr _ -> termNameFromSource expr
+ S.Negate expr -> toTermName' expr
+ S.Rescue args _ -> intercalate ", " $ toTermName' <$> args
where toTermName' = toTermName source
termNameFromChildren term children = termNameFromRange (unionRangesFrom (range term) (range <$> children))
termNameFromSource term = termNameFromRange (range term)
@@ -244,6 +256,20 @@ parentContexts contexts = hsep $ either identifiableDoc annotatableDoc <$> conte
where
identifiableDoc (c, t) = case c of
C.Assignment -> "in an" <+> catName c <+> "to" <+> termName t
+ C.Begin -> "in a" <+> catName c
+ C.Else -> "in an" <+> catName c
+ C.Elsif -> "in the" <+> squotes (termName t) <+> catName c
+ C.Method -> "in the" <+> squotes (termName t) <+> catName c
+ C.Ternary -> "in the" <+> squotes (termName t) <+> catName c
+ C.Ensure -> "in an" <+> catName c
+ C.Rescue -> case t of
+ "" -> "in a" <+> catName c
+ _ -> "in the" <+> squotes (termName t) <+> catName c
+ C.RescueModifier -> "in the" <+> squotes ("rescue" <+> termName t) <+> "modifier"
+ C.If -> "in the" <+> squotes (termName t) <+> catName c
+ C.Case -> "in the" <+> squotes (termName t) <+> catName c
+ C.Switch -> "in the" <+> squotes (termName t) <+> catName c
+ C.When -> "in a" <+> catName c
_ -> "in the" <+> termName t <+> catName c
annotatableDoc (c, t) = "of the" <+> squotes (termName t) <+> catName c
catName = toDoc . toCategoryName
@@ -324,7 +350,7 @@ instance HasCategory Category where
NumberLiteral -> "number"
Other s -> s
C.Pair -> "pair"
- Params -> "params"
+ C.Params -> "params"
Program -> "top level"
Regex -> "regex"
StringLiteral -> "string"
@@ -355,6 +381,15 @@ instance HasCategory Category where
C.Yield -> "yield statement"
C.Until -> "until statement"
C.Unless -> "unless statement"
+ C.Begin -> "begin statement"
+ C.Else -> "else block"
+ C.Elsif -> "elsif block"
+ C.Ensure -> "ensure block"
+ C.Rescue -> "rescue block"
+ C.RescueModifier -> "rescue modifier"
+ C.When -> "when comparison"
+ C.RescuedException -> "last exception"
+ C.Negate -> "negate"
instance HasField fields Category => HasCategory (SyntaxTerm leaf fields) where
toCategoryName = toCategoryName . category . extract
diff --git a/src/Language/Go.hs b/src/Language/Go.hs
index 68fa8312c..7f13950e3 100644
--- a/src/Language/Go.hs
+++ b/src/Language/Go.hs
@@ -35,6 +35,12 @@ termConstructor source sourceSpan name range children = case (name, children) of
[rangeClause, body] | category (extract rangeClause) == Other "range_clause" ->
S.For (toList $ unwrap rangeClause) (toList $ unwrap body)
other -> S.Error other
+ ("expression_switch_statement", children) -> case Prologue.break isCaseClause children of
+ (clauses, cases) -> do
+ clauses' <- withDefaultInfo $ S.Indexed clauses
+ withDefaultInfo $ S.Switch clauses' cases
+ where isCaseClause = (== Other "expression_case_clause") . category . extract
+
-- TODO: Handle multiple var specs
("var_declaration", varSpecs) -> withDefaultInfo . S.Indexed =<< mapM toVarDecl varSpecs
("short_var_declaration", children) -> listToVarDecls children
@@ -126,5 +132,6 @@ categoryForGoName = \case
"const_declaration" -> VarDecl
"if_statement" -> If
"for_statement" -> For
+ "expression_switch_statement" -> Switch
s -> Other (toS s)
diff --git a/src/Language/JavaScript.hs b/src/Language/JavaScript.hs
index 8122d11c0..e036d2162 100644
--- a/src/Language/JavaScript.hs
+++ b/src/Language/JavaScript.hs
@@ -41,21 +41,20 @@ termConstructor source sourceSpan name range children
S.Indexed rest -> S.Indexed $ a : rest
_ -> S.Indexed children
("comma_op", _ ) -> S.Error 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
- (x:xs) -> S.FunctionCall (cofree x) (cofree <$> xs)
+ ("function_call", _) -> case children of
+ member : args | category (extract member) == MemberAccess -> case toList (unwrap member) of
+ [target, method] -> S.MethodCall target method (toList . unwrap =<< args)
+ _ -> S.Error children
+ function : args -> S.FunctionCall function (toList . unwrap =<< args)
_ -> S.Error children
("ternary", condition : cases) -> S.Ternary condition cases
("ternary", _ ) -> S.Error children
- ("arguments", _) -> S.Args children
("var_assignment", [ x, y ]) -> S.VarAssignment x y
("var_assignment", _ ) -> S.Error children
("var_declaration", _) -> S.Indexed $ toVarDecl <$> children
("switch_statement", expr : rest) -> S.Switch expr rest
("switch_statement", _ ) -> S.Error children
- ("case", [ expr, body ]) -> S.Case expr body
+ ("case", [ expr, body ]) -> S.Case expr [body]
("case", _ ) -> S.Error children
("object", _) -> S.Object $ foldMap toTuple children
("pair", _) -> S.Fixed children
@@ -70,13 +69,14 @@ termConstructor source sourceSpan name range children
("throw_statment", _ ) -> S.Error children
("new_expression", [ expr ]) -> S.Constructor expr
("new_expression", _ ) -> S.Error children
- ("try_statement", [ body ]) -> S.Try body Nothing Nothing
- ("try_statement", [ body, catch ]) | Catch <- category (extract catch) -> S.Try body (Just catch) Nothing
- ("try_statement", [ body, finally ]) | Finally <- category (extract finally) -> S.Try body Nothing (Just finally)
- ("try_statement", [ body, catch, finally ])
- | Catch <- category (extract catch)
- , Finally <- category (extract finally) -> S.Try body (Just catch) (Just finally)
- ("try_statement", _ ) -> S.Error children
+ ("try_statement", _) -> case children of
+ [ body ] -> S.Try [body] [] Nothing Nothing
+ [ body, catch ] | Catch <- category (extract catch) -> S.Try [body] [catch] Nothing Nothing
+ [ body, finally ] | Finally <- category (extract finally) -> S.Try [body] [] Nothing (Just finally)
+ [ body, catch, finally ]
+ | Catch <- category (extract catch)
+ , Finally <- category (extract finally) -> S.Try [body] [catch] Nothing (Just finally)
+ _ -> S.Error children
("array", _) -> S.Array children
("method_definition", [ identifier, params, exprs ]) -> S.Method identifier (toList (unwrap params)) (toList (unwrap exprs))
("method_definition", [ identifier, exprs ]) -> S.Method identifier [] (toList (unwrap exprs))
diff --git a/src/Language/Ruby.hs b/src/Language/Ruby.hs
index 9f4e2c123..ffab7f311 100644
--- a/src/Language/Ruby.hs
+++ b/src/Language/Ruby.hs
@@ -2,6 +2,7 @@
module Language.Ruby where
import Data.Record
+import Data.List (partition)
import Info
import Prologue
import Source
@@ -10,7 +11,7 @@ import qualified Syntax as S
import Term
operators :: [Text]
-operators = ["and", "boolean_and", "or", "boolean_or", "bitwise_or", "bitwise_and", "shift", "relational", "comparison"]
+operators = [ "and", "boolean_and", "or", "boolean_or", "bitwise_or", "bitwise_and", "shift", "relational", "comparison" ]
functions :: [Text]
functions = [ "lambda_literal", "lambda_expression" ]
@@ -24,59 +25,96 @@ termConstructor
-> IO (Term (S.Syntax Text) (Record '[Range, Category, SourceSpan])) -- ^ The resulting term, in IO.
termConstructor source sourceSpan name range children
| name == "ERROR" = withDefaultInfo (S.Error children)
+ | name == "unless_modifier" = case children of
+ [ lhs, rhs ] -> do
+ condition <- withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)
+ withDefaultInfo $ S.If condition [lhs]
+ _ -> withDefaultInfo $ S.Error children
+ | name == "unless_statement" = case children of
+ ( expr : rest ) -> do
+ condition <- withRecord (setCategory (extract expr) Negate) (S.Negate expr)
+ withDefaultInfo $ S.If condition rest
+ _ -> withDefaultInfo $ S.Error children
+ | name == "until_modifier" = case children of
+ [ lhs, rhs ] -> do
+ condition <- withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)
+ withDefaultInfo $ S.While condition [lhs]
+ _ -> withDefaultInfo $ S.Error children
+ | name == "until_statement" = case children of
+ ( expr : rest ) -> do
+ condition <- withRecord (setCategory (extract expr) Negate) (S.Negate expr)
+ withDefaultInfo $ S.While condition rest
+ _ -> withDefaultInfo $ S.Error children
| otherwise = withDefaultInfo $ case (name, children) of
- ("argument_list", _) -> S.Args children
- ("array", _) -> S.Array children
+ ("array", _ ) -> S.Array children
("assignment", [ identifier, value ]) -> S.Assignment identifier value
("assignment", _ ) -> S.Error children
- ("case_statement", expr : rest) -> S.Switch expr rest
+ ("begin_statement", _ ) -> case partition (\x -> category (extract x) == Rescue) children of
+ (rescues, rest) -> case partition (\x -> category (extract x) == Ensure || category (extract x) == Else) rest of
+ (ensureElse, body) -> case ensureElse of
+ [ elseBlock, ensure ]
+ | Else <- category (extract elseBlock)
+ , Ensure <- category (extract ensure) -> S.Try body rescues (Just elseBlock) (Just ensure)
+ [ ensure, elseBlock ]
+ | Ensure <- category (extract ensure)
+ , Else <- category (extract elseBlock) -> S.Try body rescues (Just elseBlock) (Just ensure)
+ [ elseBlock ] | Else <- category (extract elseBlock) -> S.Try body rescues (Just elseBlock) Nothing
+ [ ensure ] | Ensure <- category (extract ensure) -> S.Try body rescues Nothing (Just ensure)
+ _ -> S.Try body rescues Nothing Nothing
+ ("case_statement", expr : body ) -> S.Switch expr body
("case_statement", _ ) -> S.Error children
+ ("when_block", condition : body ) -> S.Case condition body
+ ("when_block", _ ) -> S.Error children
("class_declaration", [ identifier, superclass, definitions ]) -> S.Class identifier (Just superclass) (toList (unwrap definitions))
("class_declaration", [ identifier, definitions ]) -> S.Class identifier Nothing (toList (unwrap definitions))
("class_declaration", _ ) -> S.Error children
- ("comment", _) -> S.Comment . toText $ slice range source
+ ("comment", _ ) -> S.Comment . toText $ slice range source
("conditional_assignment", [ identifier, value ]) -> S.ConditionalAssignment identifier value
("conditional_assignment", _ ) -> S.Error children
("conditional", condition : cases) -> S.Ternary condition cases
("conditional", _ ) -> S.Error 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
- (x:xs) -> S.FunctionCall (cofree x) (cofree <$> xs)
+ ("function_call", _ ) -> case children of
+ member : args | category (extract member) == MemberAccess -> case toList (unwrap member) of
+ [target, method] -> S.MethodCall target method (toList . unwrap =<< args)
+ _ -> S.Error children
+ function : args -> S.FunctionCall function (toList . unwrap =<< args)
_ -> S.Error children
- ("hash", _) -> S.Object $ foldMap toTuple children
+ ("hash", _ ) -> S.Object $ foldMap toTuple children
("if_modifier", [ lhs, condition ]) -> S.If condition [lhs]
("if_modifier", _ ) -> S.Error children
- ("if_statement", expr : rest ) -> S.If expr rest
+ ("if_statement", condition : body ) -> S.If condition body
("if_statement", _ ) -> S.Error children
+ ("elsif_block", condition : body ) -> S.If condition body
+ ("elsif_block", _ ) -> S.Error children
("element_reference", [ base, element ]) -> S.SubscriptAccess base element
("element_reference", _ ) -> S.Error children
+ ("for_statement", lhs : expr : rest ) -> S.For [lhs, expr] rest
+ ("for_statement", _ ) -> S.Error children
("math_assignment", [ identifier, value ]) -> S.MathAssignment identifier value
("math_assignment", _ ) -> S.Error children
("member_access", [ base, property ]) -> S.MemberAccess base property
("member_access", _ ) -> S.Error children
- ("method_declaration", [ identifier, params, exprs ]) -> S.Method identifier (toList (unwrap params)) (toList (unwrap exprs))
- ("method_declaration", [ identifier, exprs ]) -> S.Method identifier [] (toList (unwrap exprs))
- ("method_declaration", _ ) -> S.Error children
+ ("method_declaration", _ ) -> case children of
+ identifier : params : body | Params <- category (extract params) -> S.Method identifier (toList (unwrap params)) body
+ identifier : body -> S.Method identifier [] body
+ _ -> S.Error children
("module_declaration", identifier : body ) -> S.Module identifier body
("module_declaration", _ ) -> S.Error children
+ ("rescue_block", _ ) -> case children of
+ args : lastException : rest
+ | Args <- category (extract args)
+ , RescuedException <- category (extract lastException) -> S.Rescue (toList (unwrap args) <> [lastException]) rest
+ lastException : rest | RescuedException <- category (extract lastException) -> S.Rescue [lastException] rest
+ args : body | Args <- category (extract args) -> S.Rescue (toList (unwrap args)) body
+ body -> S.Rescue [] body
+ ("rescue_modifier", [lhs, rhs] ) -> S.Rescue [lhs] [rhs]
+ ("rescue_modifier", _ ) -> S.Error children
("return_statement", _ ) -> S.Return (listToMaybe children)
- ("unless_modifier", [ lhs, condition ]) -> S.Unless condition [lhs]
- ("unless_modifier", _ ) -> S.Error children
- ("unless_statement", expr : rest ) -> S.Unless expr rest
- ("unless_statement", _ ) -> S.Error children
- ("until_modifier", [ lhs, condition ]) -> S.Until condition [lhs]
- ("until_modifier", _ ) -> S.Error children
- ("until_statement", expr : rest ) -> S.Until expr rest
- ("until_statement", _ ) -> S.Error children
("while_modifier", [ lhs, condition ]) -> S.While condition [lhs]
("while_modifier", _ ) -> S.Error children
("while_statement", expr : rest ) -> S.While expr rest
("while_statement", _ ) -> S.Error children
- ("yield", _) -> S.Yield (listToMaybe children)
- ("for_statement", lhs : expr : rest ) -> S.For [lhs, expr] rest
- ("for_statement", _ ) -> S.Error children
+ ("yield", _ ) -> S.Yield (listToMaybe children)
_ | name `elem` operators -> S.Operator children
_ | name `elem` functions -> case children of
[ body ] -> S.AnonymousFunction [] [body]
@@ -85,9 +123,13 @@ termConstructor source sourceSpan name range children
(_, []) -> S.Leaf . toText $ slice range source
_ -> S.Indexed children
where
- withDefaultInfo syntax = do
+ withRecord record syntax = pure $! cofree (record :< syntax)
+ withCategory category syntax = do
sourceSpan' <- sourceSpan
- pure $! cofree ((range .: categoryForRubyName name .: sourceSpan' .: RNil) :< syntax)
+ pure $! cofree ((range .: category .: sourceSpan' .: RNil) :< syntax)
+ withDefaultInfo syntax = case syntax of
+ S.MethodCall{} -> withCategory MethodCall syntax
+ _ -> withCategory (categoryForRubyName name) syntax
categoryForRubyName :: Text -> Category
categoryForRubyName = \case
@@ -95,22 +137,22 @@ categoryForRubyName = \case
"argument_list" -> Args
"array" -> ArrayLiteral
"assignment" -> Assignment
- "begin_statement" -> ExpressionStatements
+ "begin_statement" -> Begin
"bitwise_and" -> BitwiseOperator -- bitwise and, e.g &.
"bitwise_or" -> BitwiseOperator -- bitwise or, e.g. ^, |.
"boolean_and" -> BooleanOperator -- boolean and, e.g. &&.
"boolean_or" -> BooleanOperator -- boolean or, e.g. &&.
"boolean" -> Boolean
- "case_statement" -> Switch
+ "case_statement" -> Case
"class_declaration" -> Class
"comment" -> Comment
"comparison" -> RelationalOperator -- comparison operator, e.g. <, <=, >=, >.
"conditional_assignment" -> ConditionalAssignment
"conditional" -> Ternary
"element_reference" -> SubscriptAccess
- "else_block" -> ExpressionStatements
- "elsif_block" -> ExpressionStatements
- "ensure_block" -> ExpressionStatements
+ "else_block" -> Else
+ "elsif_block" -> Elsif
+ "ensure_block" -> Ensure
"ERROR" -> Error
"float" -> NumberLiteral
"for_statement" -> For
@@ -123,6 +165,7 @@ categoryForRubyName = \case
"if_statement" -> If
"integer" -> IntegerLiteral
"interpolation" -> Interpolation
+ "rescued_exception" -> RescuedException
"math_assignment" -> MathAssignment
"member_access" -> MemberAccess
"method_declaration" -> Method
@@ -132,18 +175,18 @@ categoryForRubyName = \case
"program" -> Program
"regex" -> Regex
"relational" -> RelationalOperator -- relational operator, e.g. ==, !=, ===, <=>, =~, !~.
- "rescue_block" -> ExpressionStatements
+ "rescue_block" -> Rescue
+ "rescue_modifier" -> RescueModifier
"return_statement" -> Return
"shift" -> BitwiseOperator -- bitwise shift, e.g <<, >>.
"string" -> StringLiteral
"subshell" -> Subshell
"symbol" -> SymbolLiteral
- "then_block" -> ExpressionStatements
"unless_modifier" -> Unless
"unless_statement" -> Unless
"until_modifier" -> Until
"until_statement" -> Until
- "when_block" -> ExpressionStatements
+ "when_block" -> When
"while_modifier" -> While
"while_statement" -> While
"yield" -> Yield
diff --git a/src/Renderer/JSON.hs b/src/Renderer/JSON.hs
index 4d8f34e27..c3178fc49 100644
--- a/src/Renderer/JSON.hs
+++ b/src/Renderer/JSON.hs
@@ -100,7 +100,6 @@ syntaxToTermField syntax = case syntax of
S.MathAssignment identifier value -> [ "identifier" .= identifier ] <> [ "value" .= value ]
S.MemberAccess identifier value -> [ "identifier" .= identifier ] <> [ "value" .= value ]
S.MethodCall identifier methodIdentifier parameters -> [ "identifier" .= identifier ] <> [ "methodIdentifier" .= methodIdentifier ] <> [ "parameters" .= parameters ]
- S.Args c -> childrenFields c
S.Operator syntaxes -> [ "operatorSyntaxes" .= syntaxes ]
S.VarDecl declaration -> [ "declaration" .= declaration ]
S.VarAssignment identifier value -> [ "identifier" .= identifier ] <> [ "value" .= value ]
@@ -118,7 +117,7 @@ syntaxToTermField syntax = case syntax of
S.Return expression -> [ "expression" .= expression ]
S.Throw c -> [ "expression" .= c ]
S.Constructor expression -> [ "expression" .= expression ]
- S.Try body catchExpression finallyExpression -> [ "body" .= body ] <> [ "catchExpression" .= catchExpression ] <> [ "finallyExpression" .= finallyExpression ]
+ S.Try body catchExpression elseExpression finallyExpression -> [ "body" .= body ] <> [ "catchExpression" .= catchExpression ] <> [ "elseExpression" .= elseExpression ] <> [ "finallyExpression" .= finallyExpression ]
S.Array c -> childrenFields c
S.Class identifier superclass definitions -> [ "identifier" .= identifier ] <> [ "superclass" .= superclass ] <> [ "definitions" .= definitions ]
S.Method identifier parameters definitions -> [ "identifier" .= identifier ] <> [ "parameters" .= parameters ] <> [ "definitions" .= definitions ]
@@ -128,6 +127,6 @@ syntaxToTermField syntax = case syntax of
S.Export identifier statements -> [ "identifier" .= identifier ] <> [ "statements" .= statements ]
S.ConditionalAssignment id value -> [ "conditionalIdentifier" .= id ] <> [ "value" .= value ]
S.Yield expr -> [ "yieldExpression" .= expr ]
- S.Until expr body -> [ "untilExpr" .= expr ] <> [ "untilBody" .= body ]
- S.Unless expr clauses -> [ "unless" .= expr ] <> childrenFields clauses
+ S.Negate expr -> [ "negate" .= expr ]
+ S.Rescue args expressions -> [ "args" .= args ] <> childrenFields expressions
where childrenFields c = [ "children" .= c ]
diff --git a/src/Renderer/Split.hs b/src/Renderer/Split.hs
index 4659e7d00..5a49c6b45 100644
--- a/src/Renderer/Split.hs
+++ b/src/Renderer/Split.hs
@@ -57,7 +57,7 @@ styleName category = "category-" <> case category of
TemplateString -> "template_string"
Regex -> "regex"
Identifier -> "identifier"
- Params -> "parameters"
+ C.Params -> "parameters"
ExpressionStatements -> "expression_statements"
C.MathAssignment -> "math_assignment"
C.SubscriptAccess -> "subscript_access"
@@ -90,6 +90,15 @@ styleName category = "category-" <> case category of
C.Yield -> "yield_statement"
C.Until -> "until"
C.Unless -> "unless_statement"
+ C.Begin -> "begin_statement"
+ C.Else -> "else_block"
+ C.Elsif -> "elsif_block"
+ C.Ensure -> "ensure_block"
+ C.Rescue -> "rescue_block"
+ C.RescueModifier -> "rescue_modifier"
+ C.When -> "when_block"
+ C.RescuedException -> "last_exception"
+ C.Negate -> "negate"
-- | Pick the class name for a split patch.
splitPatchToClassName :: SplitPatch a -> AttributeValue
diff --git a/src/Syntax.hs b/src/Syntax.hs
index 26d205450..e3763fb1f 100644
--- a/src/Syntax.hs
+++ b/src/Syntax.hs
@@ -36,9 +36,6 @@ data Syntax a f
-- | A method call consisting of its target, the method name, and the parameters passed to the method.
-- | e.g. in Javascript console.log('hello') represents a method call.
| MethodCall { targetId :: f, methodId :: f, methodParams :: [f] }
- -- | The list of arguments to a method call.
- -- | TODO: It might be worth removing this and using Fixed instead.
- | Args [f]
-- | An operator can be applied to a list of syntaxes.
| Operator [f]
-- | A variable declaration. e.g. var foo;
@@ -49,7 +46,7 @@ data Syntax a f
-- | e.g. in Javascript x["y"] represents a subscript access syntax.
| SubscriptAccess { subscriptId :: f, subscriptElement :: f }
| Switch { switchExpr :: f, cases :: [f] }
- | Case { caseExpr :: f, caseStatements :: f }
+ | Case { caseExpr :: f, caseStatements :: [f] }
| Object { keyValues :: [f] }
-- | A pair in an Object. e.g. foo: bar or foo => bar
| Pair f f
@@ -65,7 +62,8 @@ data Syntax a f
| Return (Maybe f)
| Throw f
| Constructor f
- | Try f (Maybe f) (Maybe f)
+ -- | TODO: Is it a problem that in Ruby, this pattern can work for method def too?
+ | Try { tryBegin :: [f], catchRescue :: [f], beginElse :: Maybe f, finallyEnsure :: Maybe f }
-- | An array literal with list of children.
| Array [f]
-- | A class with an identifier, superclass, and a list of definitions.
@@ -81,9 +79,10 @@ data Syntax a f
-- | A conditional assignment represents expressions whose operator classifies as conditional (e.g. ||= or &&=).
| ConditionalAssignment { conditionalAssignmentId :: f, value :: f }
| Yield (Maybe f)
- | Until { untilExpr :: f, untilBody :: [f] }
- -- | An unless statement with an expression and maybe more expression clauses.
- | Unless f [f]
+ -- | A negation of a single expression.
+ | Negate f
+ -- | A rescue block has a list of arguments to rescue and a list of expressions.
+ | Rescue [f] [f]
deriving (Eq, Foldable, Functor, Generic, Generic1, Mergeable, Ord, Show, Traversable, ToJSON)
diff --git a/test/IntegrationFormatSpec.hs b/test/IntegrationFormatSpec.hs
index 8b84ad364..b8765019c 100644
--- a/test/IntegrationFormatSpec.hs
+++ b/test/IntegrationFormatSpec.hs
@@ -2,6 +2,7 @@ module IntegrationFormatSpec where
import Arguments
import Data.Aeson
+import Data.List.Split
import Control.Exception
import qualified Data.ByteString.Lazy as DL
import JSONTestCase
@@ -21,10 +22,11 @@ catchException = handle errorHandler
assertDiffSummary :: JSONTestCase -> Format -> (Either String ExpectedResult -> Either String ExpectedResult -> Expectation) -> Expectation
assertDiffSummary JSONTestCase {..} format matcher = do
- diffs <- fetchDiffs $ args gitDir sha1 sha2 filePaths format
+ diffs <- fetchDiffs $ args gitDir (Prelude.head shas') (Prelude.last shas') filePaths format
result <- catchException . pure . pure . concatOutputs $ diffs
let actual = eitherDecode . DL.fromStrict . encodeUtf8 . fromJust . listToMaybe $ result
matcher actual (Right expectedResult)
+ where shas' = splitOn ".." shas
runTestsIn :: [FilePath] -> Format -> (Either String ExpectedResult -> Either String ExpectedResult -> Expectation) -> SpecWith ()
runTestsIn filePaths format matcher = do
diff --git a/test/JSONTestCase.hs b/test/JSONTestCase.hs
index 31dc6ebb6..9020a1406 100644
--- a/test/JSONTestCase.hs
+++ b/test/JSONTestCase.hs
@@ -15,7 +15,8 @@ data JSONMetaRepo = JSONMetaRepo { repoUrl :: !String
, templateText :: !(Maybe String)
} deriving (Show, Generic, FromJSON)
-data JSONMetaSyntax = JSONMetaSyntax { syntax :: !String
+data JSONMetaSyntax = JSONMetaSyntax { template :: !(Maybe String)
+ , syntax :: !String
, insert :: !String
, replacement :: !String
} deriving (Show, Generic, FromJSON)
@@ -23,8 +24,8 @@ data JSONMetaSyntax = JSONMetaSyntax { syntax :: !String
data JSONTestCase = JSONTestCase { gitDir :: !String
, testCaseDescription :: !String
, filePaths :: ![String]
- , sha1 :: !String
- , sha2 :: !String
+ , shas :: !String
+ , patch :: ![String]
, expectedResult :: !ExpectedResult
} deriving (Show, Generic, FromJSON)
diff --git a/test/corpus/diff-summaries-todo/javascript/boolean-operator.json b/test/corpus/diff-summaries-todo/javascript/boolean-operator.json
index 602c44b3b..d37901088 100644
--- a/test/corpus/diff-summaries-todo/javascript/boolean-operator.json
+++ b/test/corpus/diff-summaries-todo/javascript/boolean-operator.json
@@ -9,9 +9,9 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "c57d91166c3246b8e352252024dc21de6a42f707",
+ "patch": [],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "244097ce5a74d6275f249d5159a6a14696a1eddf"
+ "shas": "c57d91166c3246b8e352252024dc21de6a42f707..244097ce5a74d6275f249d5159a6a14696a1eddf"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-test",
@@ -24,7 +24,7 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "244097ce5a74d6275f249d5159a6a14696a1eddf",
+ "patch": [],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0abfc815d9c5912259cfc25becb398a8f1444d40"
+ "shas": "244097ce5a74d6275f249d5159a6a14696a1eddf..0abfc815d9c5912259cfc25becb398a8f1444d40"
}]
diff --git a/test/corpus/diff-summaries-todo/javascript/relational-operator.json b/test/corpus/diff-summaries-todo/javascript/relational-operator.json
index 9c30b3b98..c292162a4 100644
--- a/test/corpus/diff-summaries-todo/javascript/relational-operator.json
+++ b/test/corpus/diff-summaries-todo/javascript/relational-operator.json
@@ -9,9 +9,9 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "f79a619c0277b82bb45cb1510847b78ba44ea31b",
+ "patch": [],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1fc7441b1fb64b171cf7892e3ce25bc55e25d754"
+ "shas": "f79a619c0277b82bb45cb1510847b78ba44ea31b..1fc7441b1fb64b171cf7892e3ce25bc55e25d754"
}
,{
"testCaseDescription": "javascript-relational-operator-replacement-test",
@@ -24,7 +24,7 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "1fc7441b1fb64b171cf7892e3ce25bc55e25d754",
+ "patch": [],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e1d768da1e35b8066276dc5b5f9653442345948d"
+ "shas": "1fc7441b1fb64b171cf7892e3ce25bc55e25d754..e1d768da1e35b8066276dc5b5f9653442345948d"
}]
diff --git a/test/corpus/diff-summaries-todo/ruby/control-statements.json b/test/corpus/diff-summaries-todo/ruby/control-statements.json
deleted file mode 100644
index ddbe060f1..000000000
--- a/test/corpus/diff-summaries-todo/ruby/control-statements.json
+++ /dev/null
@@ -1,241 +0,0 @@
-[{
- "testCaseDescription": "ruby-control-statements-insert-test",
- "expectedResult": {
- "changes": {
- "control-statements.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 2,
- 2
- ],
- "end": [
- 2,
- 5
- ]
- }
- },
- "summary": "Added a begin block"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "control-statements.rb"
- ],
- "sha1": "0afd2cfcf489061cc131d9970716bb04bb5cb203",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "703d5515f05e02ad93d56987b520328f4a351265"
-}
-,{
- "testCaseDescription": "ruby-control-statements-replacement-insert-test",
- "expectedResult": {
- "changes": {
- "control-statements.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 2,
- 4
- ]
- }
- },
- "summary": "Added a begin block"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "control-statements.rb"
- ],
- "sha1": "703d5515f05e02ad93d56987b520328f4a351265",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "554242b8ed778be509d72c90b71381c7a49c5bf4"
-}
-,{
- "testCaseDescription": "ruby-control-statements-delete-insert-test",
- "expectedResult": {
- "changes": {
- "control-statements.rb": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 2,
- 4
- ]
- },
- {
- "start": [
- 2,
- 2
- ],
- "end": [
- 2,
- 5
- ]
- }
- ]
- },
- "summary": "Replaced a begin block with a begin block"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "control-statements.rb"
- ],
- "sha1": "554242b8ed778be509d72c90b71381c7a49c5bf4",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "bd0b46ca0ec2510b867cc5670fbafb0068db0d9c"
-}
-,{
- "testCaseDescription": "ruby-control-statements-replacement-test",
- "expectedResult": {
- "changes": {
- "control-statements.rb": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 2,
- 2
- ],
- "end": [
- 2,
- 5
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 2,
- 4
- ]
- }
- ]
- },
- "summary": "Replaced a begin block with a begin block"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "control-statements.rb"
- ],
- "sha1": "bd0b46ca0ec2510b867cc5670fbafb0068db0d9c",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "3a174f29f8c703fdb1ebf05ef9ef856550f3b968"
-}
-,{
- "testCaseDescription": "ruby-control-statements-delete-replacement-test",
- "expectedResult": {
- "changes": {
- "control-statements.rb": [
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 2,
- 4
- ]
- }
- },
- "summary": "Deleted a begin block"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "control-statements.rb"
- ],
- "sha1": "3a174f29f8c703fdb1ebf05ef9ef856550f3b968",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "5dc5bafea85edc0573668d9b80192e910150caf3"
-}
-,{
- "testCaseDescription": "ruby-control-statements-delete-test",
- "expectedResult": {
- "changes": {
- "control-statements.rb": [
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 3
- ],
- "end": [
- 8,
- 6
- ]
- }
- },
- "summary": "Deleted the 'baz' identifier"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "control-statements.rb"
- ],
- "sha1": "5dc5bafea85edc0573668d9b80192e910150caf3",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "8cde2cc96f0eef72794161e18540bbb43a24937d"
-}
-,{
- "testCaseDescription": "ruby-control-statements-delete-rest-test",
- "expectedResult": {
- "changes": {
- "control-statements.rb": [
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 2,
- 4
- ]
- }
- },
- "summary": "Deleted a begin block"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "control-statements.rb"
- ],
- "sha1": "8cde2cc96f0eef72794161e18540bbb43a24937d",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "457dc7fc963751d0adf0ea4eb8934e39ef717e32"
-}]
diff --git a/test/corpus/diff-summaries/go/array-types.json b/test/corpus/diff-summaries/go/array-types.json
index 0d17d03b9..752cc75d3 100644
--- a/test/corpus/diff-summaries/go/array-types.json
+++ b/test/corpus/diff-summaries/go/array-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
11
],
"end": [
- 3,
+ 1,
12
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
14
]
}
@@ -70,9 +70,16 @@
"filePaths": [
"array-types.go"
],
- "sha1": "6d7202f99aff5a0fefda7df058917f141335424f",
+ "patch": [
+ "diff --git a/array-types.go b/array-types.go",
+ "index e69de29..f9c11b8 100644",
+ "--- a/array-types.go",
+ "+++ b/array-types.go",
+ "@@ -0,0 +1 @@",
+ "+type a [2+2]x"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e22dc38811887835cdba8d7d0f0e3edfa6930c56"
+ "shas": "96ee23366cb8e34e0b1aef14810c83f5066a6f3b..f25c42f9d50f3a4f670ca6d82cb7120feb42e472"
}
,{
"testCaseDescription": "go-array-types-replacement-insert-test",
@@ -83,11 +90,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -98,11 +105,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -113,11 +120,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
11
],
"end": [
- 3,
+ 1,
12
]
}
@@ -128,11 +135,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
14
]
}
@@ -143,11 +150,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -158,11 +165,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
}
@@ -173,11 +180,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
11
],
"end": [
- 4,
+ 2,
12
]
}
@@ -188,11 +195,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
13
],
"end": [
- 4,
+ 2,
14
]
}
@@ -206,9 +213,18 @@
"filePaths": [
"array-types.go"
],
- "sha1": "e22dc38811887835cdba8d7d0f0e3edfa6930c56",
+ "patch": [
+ "diff --git a/array-types.go b/array-types.go",
+ "index f9c11b8..d2b8166 100644",
+ "--- a/array-types.go",
+ "+++ b/array-types.go",
+ "@@ -1 +1,3 @@",
+ "+type a [1+1]y",
+ "+type a [2+2]x",
+ " type a [2+2]x"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "31d6f9d239697a44741a23a1b37e6c2de4d70ddb"
+ "shas": "f25c42f9d50f3a4f670ca6d82cb7120feb42e472..159e876dd37dd92c673a5d42908dd4e39437c427"
}
,{
"testCaseDescription": "go-array-types-delete-insert-test",
@@ -220,21 +236,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
},
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -247,21 +263,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
11
],
"end": [
- 3,
+ 1,
12
]
},
{
"start": [
- 3,
+ 1,
11
],
"end": [
- 3,
+ 1,
12
]
}
@@ -274,21 +290,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
14
]
},
{
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
14
]
}
@@ -303,9 +319,19 @@
"filePaths": [
"array-types.go"
],
- "sha1": "31d6f9d239697a44741a23a1b37e6c2de4d70ddb",
+ "patch": [
+ "diff --git a/array-types.go b/array-types.go",
+ "index d2b8166..823c5f1 100644",
+ "--- a/array-types.go",
+ "+++ b/array-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-type a [1+1]y",
+ "+type a [2+2]x",
+ " type a [2+2]x",
+ " type a [2+2]x"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "5f10f74b19bad493aea3a99c580e80e024e036fc"
+ "shas": "159e876dd37dd92c673a5d42908dd4e39437c427..d1f1827268467008a98150e05dbd55c35a6c158a"
}
,{
"testCaseDescription": "go-array-types-replacement-test",
@@ -317,21 +343,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
},
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -344,21 +370,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
11
],
"end": [
- 3,
+ 1,
12
]
},
{
"start": [
- 3,
+ 1,
11
],
"end": [
- 3,
+ 1,
12
]
}
@@ -371,21 +397,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
14
]
},
{
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
14
]
}
@@ -400,9 +426,19 @@
"filePaths": [
"array-types.go"
],
- "sha1": "5f10f74b19bad493aea3a99c580e80e024e036fc",
+ "patch": [
+ "diff --git a/array-types.go b/array-types.go",
+ "index 823c5f1..d2b8166 100644",
+ "--- a/array-types.go",
+ "+++ b/array-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-type a [2+2]x",
+ "+type a [1+1]y",
+ " type a [2+2]x",
+ " type a [2+2]x"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c79b560d124a946f56465001dc8f25492ec14de6"
+ "shas": "d1f1827268467008a98150e05dbd55c35a6c158a..1458fd09e1ef2e04e8b8ef9f689c2c1c97f51537"
}
,{
"testCaseDescription": "go-array-types-delete-replacement-test",
@@ -413,11 +449,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -428,11 +464,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -443,11 +479,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
11
],
"end": [
- 3,
+ 1,
12
]
}
@@ -458,11 +494,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
14
]
}
@@ -473,11 +509,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -488,11 +524,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
}
@@ -503,11 +539,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
11
],
"end": [
- 4,
+ 2,
12
]
}
@@ -518,11 +554,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
13
],
"end": [
- 4,
+ 2,
14
]
}
@@ -533,11 +569,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -548,11 +584,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
}
@@ -563,11 +599,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
11
],
"end": [
- 4,
+ 2,
12
]
}
@@ -578,11 +614,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
13
],
"end": [
- 4,
+ 2,
14
]
}
@@ -596,9 +632,19 @@
"filePaths": [
"array-types.go"
],
- "sha1": "c79b560d124a946f56465001dc8f25492ec14de6",
+ "patch": [
+ "diff --git a/array-types.go b/array-types.go",
+ "index d2b8166..5b93d14 100644",
+ "--- a/array-types.go",
+ "+++ b/array-types.go",
+ "@@ -1,3 +1,2 @@",
+ "-type a [1+1]y",
+ "-type a [2+2]x",
+ " type a [2+2]x",
+ "+type a [1+1]y"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "eada01132d5a174337533994662482da20adf753"
+ "shas": "1458fd09e1ef2e04e8b8ef9f689c2c1c97f51537..c9e35d61508072dac51659d61f747dbb40ed1409"
}
,{
"testCaseDescription": "go-array-types-delete-test",
@@ -609,11 +655,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -624,11 +670,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -639,11 +685,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
11
],
"end": [
- 3,
+ 1,
12
]
}
@@ -654,11 +700,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
14
]
}
@@ -672,9 +718,17 @@
"filePaths": [
"array-types.go"
],
- "sha1": "eada01132d5a174337533994662482da20adf753",
+ "patch": [
+ "diff --git a/array-types.go b/array-types.go",
+ "index 5b93d14..967447e 100644",
+ "--- a/array-types.go",
+ "+++ b/array-types.go",
+ "@@ -1,2 +1 @@",
+ "-type a [2+2]x",
+ " type a [1+1]y"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "28132de0b90eb8588e880b7237e7242e3195076c"
+ "shas": "c9e35d61508072dac51659d61f747dbb40ed1409..c6480a6cc44a0b8d54aec67dda72e6a765acace9"
}
,{
"testCaseDescription": "go-array-types-delete-rest-test",
@@ -685,11 +739,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -700,11 +754,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -715,11 +769,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
11
],
"end": [
- 3,
+ 1,
12
]
}
@@ -730,11 +784,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
14
]
}
@@ -748,7 +802,14 @@
"filePaths": [
"array-types.go"
],
- "sha1": "28132de0b90eb8588e880b7237e7242e3195076c",
+ "patch": [
+ "diff --git a/array-types.go b/array-types.go",
+ "index 967447e..e69de29 100644",
+ "--- a/array-types.go",
+ "+++ b/array-types.go",
+ "@@ -1 +0,0 @@",
+ "-type a [1+1]y"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "4c8c99e5a735f66e43d41e65a75a75272a162c8c"
+ "shas": "c6480a6cc44a0b8d54aec67dda72e6a765acace9..338fc2d73f62d9c316e48cf2390c1052834d4985"
}]
diff --git a/test/corpus/diff-summaries/go/array-with-implicit-length.json b/test/corpus/diff-summaries/go/array-with-implicit-length.json
index c0a13558b..688c2ee10 100644
--- a/test/corpus/diff-summaries/go/array-with-implicit-length.json
+++ b/test/corpus/diff-summaries/go/array-with-implicit-length.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
29
]
}
@@ -25,9 +25,16 @@
"filePaths": [
"array-with-implicit-length.go"
],
- "sha1": "ac21f9d0ee6f7ef2a5a607b08fe2b95f3a6470c8",
+ "patch": [
+ "diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
+ "index e69de29..96bef76 100644",
+ "--- a/array-with-implicit-length.go",
+ "+++ b/array-with-implicit-length.go",
+ "@@ -0,0 +1 @@",
+ "+const a1 = [...]int{1, 2, 3}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b2003e760af2573de2e6b858f19cfdf65c60e100"
+ "shas": "5b7d43722e8258820bec8f43f32d77913026fbd1..edcc037141ca5e780da35e91b330a260a8f79838"
}
,{
"testCaseDescription": "go-array-with-implicit-length-replacement-insert-test",
@@ -38,11 +45,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
27
]
}
@@ -53,11 +60,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
29
]
}
@@ -71,9 +78,18 @@
"filePaths": [
"array-with-implicit-length.go"
],
- "sha1": "b2003e760af2573de2e6b858f19cfdf65c60e100",
+ "patch": [
+ "diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
+ "index 96bef76..f49bee5 100644",
+ "--- a/array-with-implicit-length.go",
+ "+++ b/array-with-implicit-length.go",
+ "@@ -1 +1,3 @@",
+ "+const a1 = [...]int{4,5,6}",
+ "+const a1 = [...]int{1, 2, 3}",
+ " const a1 = [...]int{1, 2, 3}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b9540f341273e90a488fdfb2bbd606bccf787d36"
+ "shas": "edcc037141ca5e780da35e91b330a260a8f79838..7d1007d97d728e64ee552482159b4198342facfe"
}
,{
"testCaseDescription": "go-array-with-implicit-length-delete-insert-test",
@@ -85,84 +101,84 @@
"replace": [
{
"start": [
- 3,
+ 1,
21
],
"end": [
- 3,
+ 1,
22
]
},
{
"start": [
- 3,
+ 1,
21
],
"end": [
- 3,
+ 1,
22
]
}
]
},
- "summary": "Replaced '4' with '1' in the a1 variable of the 'main' module"
+ "summary": "Replaced '4' with '1' in the a1 variable"
},
{
"span": {
"insert": {
"start": [
- 3,
+ 1,
24
],
"end": [
- 3,
+ 1,
25
]
}
},
- "summary": "Added '2' in the a1 variable of the 'main' module"
+ "summary": "Added '2' in the a1 variable"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
23
],
"end": [
- 3,
+ 1,
24
]
},
{
"start": [
- 3,
+ 1,
27
],
"end": [
- 3,
+ 1,
28
]
}
]
},
- "summary": "Replaced '5' with '3' in the a1 variable of the 'main' module"
+ "summary": "Replaced '5' with '3' in the a1 variable"
},
{
"span": {
"delete": {
"start": [
- 3,
+ 1,
25
],
"end": [
- 3,
+ 1,
26
]
}
},
- "summary": "Deleted '6' in the a1 variable of the 'main' module"
+ "summary": "Deleted '6' in the a1 variable"
}
]
},
@@ -171,9 +187,19 @@
"filePaths": [
"array-with-implicit-length.go"
],
- "sha1": "b9540f341273e90a488fdfb2bbd606bccf787d36",
+ "patch": [
+ "diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
+ "index f49bee5..9dcd627 100644",
+ "--- a/array-with-implicit-length.go",
+ "+++ b/array-with-implicit-length.go",
+ "@@ -1,3 +1,3 @@",
+ "-const a1 = [...]int{4,5,6}",
+ "+const a1 = [...]int{1, 2, 3}",
+ " const a1 = [...]int{1, 2, 3}",
+ " const a1 = [...]int{1, 2, 3}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "06870e4f83b7bd64b0d91a7087c1969a1672c48f"
+ "shas": "7d1007d97d728e64ee552482159b4198342facfe..88d19b7c4c4bf31b65d977c10679944f9f88d95b"
}
,{
"testCaseDescription": "go-array-with-implicit-length-replacement-test",
@@ -185,84 +211,84 @@
"replace": [
{
"start": [
- 3,
+ 1,
21
],
"end": [
- 3,
+ 1,
22
]
},
{
"start": [
- 3,
+ 1,
21
],
"end": [
- 3,
+ 1,
22
]
}
]
},
- "summary": "Replaced '1' with '4' in the a1 variable of the 'main' module"
+ "summary": "Replaced '1' with '4' in the a1 variable"
},
{
"span": {
"insert": {
"start": [
- 3,
+ 1,
23
],
"end": [
- 3,
+ 1,
24
]
}
},
- "summary": "Added '5' in the a1 variable of the 'main' module"
+ "summary": "Added '5' in the a1 variable"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
24
],
"end": [
- 3,
+ 1,
25
]
},
{
"start": [
- 3,
+ 1,
25
],
"end": [
- 3,
+ 1,
26
]
}
]
},
- "summary": "Replaced '2' with '6' in the a1 variable of the 'main' module"
+ "summary": "Replaced '2' with '6' in the a1 variable"
},
{
"span": {
"delete": {
"start": [
- 3,
+ 1,
27
],
"end": [
- 3,
+ 1,
28
]
}
},
- "summary": "Deleted '3' in the a1 variable of the 'main' module"
+ "summary": "Deleted '3' in the a1 variable"
}
]
},
@@ -271,9 +297,19 @@
"filePaths": [
"array-with-implicit-length.go"
],
- "sha1": "06870e4f83b7bd64b0d91a7087c1969a1672c48f",
+ "patch": [
+ "diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
+ "index 9dcd627..f49bee5 100644",
+ "--- a/array-with-implicit-length.go",
+ "+++ b/array-with-implicit-length.go",
+ "@@ -1,3 +1,3 @@",
+ "-const a1 = [...]int{1, 2, 3}",
+ "+const a1 = [...]int{4,5,6}",
+ " const a1 = [...]int{1, 2, 3}",
+ " const a1 = [...]int{1, 2, 3}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "78f16bf51a9b1140330341e26e8511bca810e7c4"
+ "shas": "88d19b7c4c4bf31b65d977c10679944f9f88d95b..905f1a72deb7cec5e88cefc93e9628cad1d4e2bc"
}
,{
"testCaseDescription": "go-array-with-implicit-length-delete-replacement-test",
@@ -284,11 +320,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
27
]
}
@@ -299,11 +335,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
29
]
}
@@ -314,11 +350,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
27
]
}
@@ -332,9 +368,19 @@
"filePaths": [
"array-with-implicit-length.go"
],
- "sha1": "78f16bf51a9b1140330341e26e8511bca810e7c4",
+ "patch": [
+ "diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
+ "index f49bee5..47b9eed 100644",
+ "--- a/array-with-implicit-length.go",
+ "+++ b/array-with-implicit-length.go",
+ "@@ -1,3 +1,2 @@",
+ "-const a1 = [...]int{4,5,6}",
+ "-const a1 = [...]int{1, 2, 3}",
+ " const a1 = [...]int{1, 2, 3}",
+ "+const a1 = [...]int{4,5,6}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e5ebc6a85298ceed84d950d738938506f90d50f1"
+ "shas": "905f1a72deb7cec5e88cefc93e9628cad1d4e2bc..fa1469f02d461361ba3454f261e10a6997fd8018"
}
,{
"testCaseDescription": "go-array-with-implicit-length-delete-test",
@@ -345,11 +391,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
29
]
}
@@ -363,9 +409,17 @@
"filePaths": [
"array-with-implicit-length.go"
],
- "sha1": "e5ebc6a85298ceed84d950d738938506f90d50f1",
+ "patch": [
+ "diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
+ "index 47b9eed..4a8295f 100644",
+ "--- a/array-with-implicit-length.go",
+ "+++ b/array-with-implicit-length.go",
+ "@@ -1,2 +1 @@",
+ "-const a1 = [...]int{1, 2, 3}",
+ " const a1 = [...]int{4,5,6}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f94dc6ba5ee00ec4ec8aeea305dc3e0cedfa95ec"
+ "shas": "fa1469f02d461361ba3454f261e10a6997fd8018..474494799fa1d5404e6f73a5a5c8511431985ee2"
}
,{
"testCaseDescription": "go-array-with-implicit-length-delete-rest-test",
@@ -376,11 +430,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
27
]
}
@@ -394,7 +448,14 @@
"filePaths": [
"array-with-implicit-length.go"
],
- "sha1": "f94dc6ba5ee00ec4ec8aeea305dc3e0cedfa95ec",
+ "patch": [
+ "diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
+ "index 4a8295f..e69de29 100644",
+ "--- a/array-with-implicit-length.go",
+ "+++ b/array-with-implicit-length.go",
+ "@@ -1 +0,0 @@",
+ "-const a1 = [...]int{4,5,6}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3003ac02afb103f388ce64e485de8c028c6eb629"
+ "shas": "474494799fa1d5404e6f73a5a5c8511431985ee2..02421320cce3bcbcdb5d7bd248eb1aa0ef8aff93"
}]
diff --git a/test/corpus/diff-summaries/go/assignment-statements.json b/test/corpus/diff-summaries/go/assignment-statements.json
index 48dc47c49..764725b1a 100644
--- a/test/corpus/diff-summaries/go/assignment-statements.json
+++ b/test/corpus/diff-summaries/go/assignment-statements.json
@@ -1,48 +1,5 @@
[{
"testCaseDescription": "go-assignment-statements-insert-test",
- "expectedResult": {
- "changes": {
- "assignment-statements.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
- },
- "summary": "Replaced the 'main' module with the 'main' module"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "assignment-statements.go"
- ],
- "sha1": "b320a69e5c137c5545033f688550f587c255cd27",
- "gitDir": "test/corpus/repos/go",
- "sha2": "8a2c5665152ae9b8684a39f596572feae6697877"
-}
-,{
- "testCaseDescription": "go-assignment-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"assignment-statements.go": [
@@ -50,161 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
- 2
- ]
- }
- },
- "summary": "Added 'x' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 3,
- 5
- ],
- "end": [
- 3,
- 6
- ]
- }
- },
- "summary": "Added '1'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 2
- ]
- }
- },
- "summary": "Added 'y' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 4
- ],
- "end": [
- 4,
- 5
- ]
- }
- },
- "summary": "Added 'c' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 9
- ],
- "end": [
- 4,
- 10
- ]
- }
- },
- "summary": "Added '2'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 12
- ],
- "end": [
- 4,
- 13
- ]
- }
- },
- "summary": "Added '3'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 1
- ],
- "end": [
- 5,
- 2
- ]
- }
- },
- "summary": "Added 'z' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 7
- ]
- }
- },
- "summary": "Added '3'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 6,
- 1
- ],
- "end": [
- 6,
- 2
- ]
- }
- },
- "summary": "Added 'h' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 6,
- 6
- ],
- "end": [
- 6,
- 7
- ]
- }
- },
- "summary": "Added '1'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 7,
- 1
- ],
- "end": [
- 7,
+ 1,
2
]
}
@@ -215,11 +22,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 1,
5
],
"end": [
- 7,
+ 1,
6
]
}
@@ -230,11 +37,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 2,
1
],
"end": [
- 8,
+ 2,
2
]
}
@@ -245,11 +52,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 2,
4
],
"end": [
- 8,
+ 2,
5
]
}
@@ -260,11 +67,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 2,
9
],
"end": [
- 8,
+ 2,
10
]
}
@@ -275,11 +82,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 2,
12
],
"end": [
- 8,
+ 2,
13
]
}
@@ -290,11 +97,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 3,
1
],
"end": [
- 9,
+ 3,
2
]
}
@@ -305,11 +112,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 3,
6
],
"end": [
- 9,
+ 3,
7
]
}
@@ -320,11 +127,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 4,
1
],
"end": [
- 10,
+ 4,
2
]
}
@@ -335,11 +142,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 4,
6
],
"end": [
- 10,
+ 4,
7
]
}
@@ -353,9 +160,352 @@
"filePaths": [
"assignment-statements.go"
],
- "sha1": "8a2c5665152ae9b8684a39f596572feae6697877",
+ "patch": [
+ "diff --git a/assignment-statements.go b/assignment-statements.go",
+ "index e69de29..91be59d 100644",
+ "--- a/assignment-statements.go",
+ "+++ b/assignment-statements.go",
+ "@@ -0,0 +1,4 @@",
+ "+a = 1",
+ "+b, c += 2, 3",
+ "+d *= 3",
+ "+e += 1"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "8732e9a5f4751218dd8c7bd121b9b3f976144143"
+ "shas": "4c2cd3b8d03249a567a8ce63cdf8b9f5e4fd098c..051ee000ea11ca989223bb2cafb2fe6d5fb8417b"
+}
+,{
+ "testCaseDescription": "go-assignment-statements-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "assignment-statements.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 2
+ ]
+ }
+ },
+ "summary": "Added 'x' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Added '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Added 'y' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 4
+ ],
+ "end": [
+ 2,
+ 5
+ ]
+ }
+ },
+ "summary": "Added 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 9
+ ],
+ "end": [
+ 2,
+ 10
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Added '3'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Added 'z' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 6
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ }
+ },
+ "summary": "Added '3'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
+ },
+ "summary": "Added 'h' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 6
+ ],
+ "end": [
+ 4,
+ 7
+ ]
+ }
+ },
+ "summary": "Added '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 5,
+ 6
+ ]
+ }
+ },
+ "summary": "Added '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ },
+ "summary": "Added 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 4
+ ],
+ "end": [
+ 6,
+ 5
+ ]
+ }
+ },
+ "summary": "Added 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 9
+ ],
+ "end": [
+ 6,
+ 10
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 12
+ ],
+ "end": [
+ 6,
+ 13
+ ]
+ }
+ },
+ "summary": "Added '3'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ }
+ },
+ "summary": "Added 'd' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 6
+ ],
+ "end": [
+ 7,
+ 7
+ ]
+ }
+ },
+ "summary": "Added '3'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 1
+ ],
+ "end": [
+ 8,
+ 2
+ ]
+ }
+ },
+ "summary": "Added 'e' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 6
+ ],
+ "end": [
+ 8,
+ 7
+ ]
+ }
+ },
+ "summary": "Added '1'"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "assignment-statements.go"
+ ],
+ "patch": [
+ "diff --git a/assignment-statements.go b/assignment-statements.go",
+ "index 91be59d..9d7456f 100644",
+ "--- a/assignment-statements.go",
+ "+++ b/assignment-statements.go",
+ "@@ -1,3 +1,11 @@",
+ "+x = 1",
+ "+y, c += 2, 3",
+ "+z *= 3",
+ "+h += 1",
+ "+a = 1",
+ "+b, c += 2, 3",
+ "+d *= 3",
+ "+e += 1",
+ " a = 1",
+ " b, c += 2, 3",
+ " d *= 3"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "051ee000ea11ca989223bb2cafb2fe6d5fb8417b..2ee13da5baeb2504510d7e1dc5ebd2e45caffd72"
}
,{
"testCaseDescription": "go-assignment-statements-delete-insert-test",
@@ -367,21 +517,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -394,21 +544,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
},
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -421,21 +571,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
},
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -447,11 +597,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -462,11 +612,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -477,11 +627,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -492,11 +642,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -510,9 +660,26 @@
"filePaths": [
"assignment-statements.go"
],
- "sha1": "8732e9a5f4751218dd8c7bd121b9b3f976144143",
+ "patch": [
+ "diff --git a/assignment-statements.go b/assignment-statements.go",
+ "index 9d7456f..87b0c42 100644",
+ "--- a/assignment-statements.go",
+ "+++ b/assignment-statements.go",
+ "@@ -1,7 +1,7 @@",
+ "-x = 1",
+ "-y, c += 2, 3",
+ "-z *= 3",
+ "-h += 1",
+ "+a = 1",
+ "+b, c += 2, 3",
+ "+d *= 3",
+ "+e += 1",
+ " a = 1",
+ " b, c += 2, 3",
+ " d *= 3"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "18263c4aaf3e218b171b61d403d2757aa28021c8"
+ "shas": "2ee13da5baeb2504510d7e1dc5ebd2e45caffd72..34bb2cd36820df90bbc0e72b4158deb44485064d"
}
,{
"testCaseDescription": "go-assignment-statements-replacement-test",
@@ -524,21 +691,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -551,21 +718,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
},
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -578,21 +745,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
},
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -604,11 +771,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -619,11 +786,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -634,11 +801,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -649,11 +816,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -667,9 +834,26 @@
"filePaths": [
"assignment-statements.go"
],
- "sha1": "18263c4aaf3e218b171b61d403d2757aa28021c8",
+ "patch": [
+ "diff --git a/assignment-statements.go b/assignment-statements.go",
+ "index 87b0c42..9d7456f 100644",
+ "--- a/assignment-statements.go",
+ "+++ b/assignment-statements.go",
+ "@@ -1,7 +1,7 @@",
+ "-a = 1",
+ "-b, c += 2, 3",
+ "-d *= 3",
+ "-e += 1",
+ "+x = 1",
+ "+y, c += 2, 3",
+ "+z *= 3",
+ "+h += 1",
+ " a = 1",
+ " b, c += 2, 3",
+ " d *= 3"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "299b0c2fe77d0bd36984a4f639b71346f9b613f2"
+ "shas": "34bb2cd36820df90bbc0e72b4158deb44485064d..0ff7c4a6db9c0607f1da6c61bd140afd1e2cd2ed"
}
,{
"testCaseDescription": "go-assignment-statements-delete-replacement-test",
@@ -680,11 +864,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -695,11 +879,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
}
@@ -710,11 +894,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -725,11 +909,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
4
],
"end": [
- 4,
+ 2,
5
]
}
@@ -740,11 +924,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
}
@@ -755,11 +939,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
}
@@ -770,11 +954,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -785,11 +969,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
@@ -800,11 +984,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -815,11 +999,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -830,11 +1014,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -845,11 +1029,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
6
]
}
@@ -860,11 +1044,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -875,11 +1059,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
4
],
"end": [
- 8,
+ 6,
5
]
}
@@ -890,11 +1074,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
9
],
"end": [
- 8,
+ 6,
10
]
}
@@ -905,11 +1089,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
12
],
"end": [
- 8,
+ 6,
13
]
}
@@ -920,11 +1104,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
2
]
}
@@ -935,11 +1119,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
7
]
}
@@ -950,11 +1134,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -965,11 +1149,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
6
],
"end": [
- 10,
+ 8,
7
]
}
@@ -980,11 +1164,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -995,11 +1179,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
6
]
}
@@ -1010,11 +1194,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -1025,11 +1209,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
4
],
"end": [
- 8,
+ 6,
5
]
}
@@ -1040,11 +1224,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
9
],
"end": [
- 8,
+ 6,
10
]
}
@@ -1055,11 +1239,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
12
],
"end": [
- 8,
+ 6,
13
]
}
@@ -1070,11 +1254,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
2
]
}
@@ -1085,11 +1269,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
7
]
}
@@ -1100,11 +1284,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -1115,11 +1299,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
6
],
"end": [
- 10,
+ 8,
7
]
}
@@ -1133,9 +1317,31 @@
"filePaths": [
"assignment-statements.go"
],
- "sha1": "299b0c2fe77d0bd36984a4f639b71346f9b613f2",
+ "patch": [
+ "diff --git a/assignment-statements.go b/assignment-statements.go",
+ "index 9d7456f..d51ed96 100644",
+ "--- a/assignment-statements.go",
+ "+++ b/assignment-statements.go",
+ "@@ -1,12 +1,8 @@",
+ "-x = 1",
+ "-y, c += 2, 3",
+ "-z *= 3",
+ "-h += 1",
+ "-a = 1",
+ "-b, c += 2, 3",
+ "-d *= 3",
+ "-e += 1",
+ " a = 1",
+ " b, c += 2, 3",
+ " d *= 3",
+ " e += 1",
+ "+x = 1",
+ "+y, c += 2, 3",
+ "+z *= 3",
+ "+h += 1"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b8fae5034ae26643f9e4f0749b6818be5c001503"
+ "shas": "0ff7c4a6db9c0607f1da6c61bd140afd1e2cd2ed..5d18144f94542fcc9740fa04c0564a62bc8360b0"
}
,{
"testCaseDescription": "go-assignment-statements-delete-test",
@@ -1146,11 +1352,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -1161,11 +1367,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
}
@@ -1176,11 +1382,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -1191,11 +1397,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
4
],
"end": [
- 4,
+ 2,
5
]
}
@@ -1206,11 +1412,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
}
@@ -1221,11 +1427,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
}
@@ -1236,11 +1442,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -1251,11 +1457,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
@@ -1266,11 +1472,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -1281,11 +1487,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -1299,9 +1505,22 @@
"filePaths": [
"assignment-statements.go"
],
- "sha1": "b8fae5034ae26643f9e4f0749b6818be5c001503",
+ "patch": [
+ "diff --git a/assignment-statements.go b/assignment-statements.go",
+ "index d51ed96..5f3e29f 100644",
+ "--- a/assignment-statements.go",
+ "+++ b/assignment-statements.go",
+ "@@ -1,7 +1,3 @@",
+ "-a = 1",
+ "-b, c += 2, 3",
+ "-d *= 3",
+ "-e += 1",
+ " x = 1",
+ " y, c += 2, 3",
+ " z *= 3"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "6ff6167c1bf691334b36eab3c3da243812e31479"
+ "shas": "5d18144f94542fcc9740fa04c0564a62bc8360b0..93d7f29bad463009b3f832561f305471e4efe373"
}
,{
"testCaseDescription": "go-assignment-statements-delete-rest-test",
@@ -1310,30 +1529,153 @@
"assignment-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 2
+ ]
+ }
},
- "summary": "Replaced 'main' module with 'main' module"
+ "summary": "Deleted 'x' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted '1'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted 'y' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 4
+ ],
+ "end": [
+ 2,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 9
+ ],
+ "end": [
+ 2,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted '2'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted '3'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted 'z' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 6
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted '3'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted 'h' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 6
+ ],
+ "end": [
+ 4,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted '1'"
}
]
},
@@ -1342,7 +1684,17 @@
"filePaths": [
"assignment-statements.go"
],
- "sha1": "6ff6167c1bf691334b36eab3c3da243812e31479",
+ "patch": [
+ "diff --git a/assignment-statements.go b/assignment-statements.go",
+ "index 5f3e29f..e69de29 100644",
+ "--- a/assignment-statements.go",
+ "+++ b/assignment-statements.go",
+ "@@ -1,4 +0,0 @@",
+ "-x = 1",
+ "-y, c += 2, 3",
+ "-z *= 3",
+ "-h += 1"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "d721dbc2d0c1b003563fe79a82b9f2d3f609cc64"
+ "shas": "93d7f29bad463009b3f832561f305471e4efe373..bd35724ed7512ba9bb228b806e5888f347bd3793"
}]
diff --git a/test/corpus/diff-summaries/go/call-expressions.json b/test/corpus/diff-summaries/go/call-expressions.json
index 451585822..6ce686827 100644
--- a/test/corpus/diff-summaries/go/call-expressions.json
+++ b/test/corpus/diff-summaries/go/call-expressions.json
@@ -5,30 +5,138 @@
"call-expressions.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 2
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'x' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 3
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 6
+ ],
+ "end": [
+ 1,
+ 7
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'y' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 6
+ ],
+ "end": [
+ 2,
+ 7
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'z' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
}
]
},
@@ -37,9 +145,18 @@
"filePaths": [
"call-expressions.go"
],
- "sha1": "b553e5d63655ec620ade647a1f3551dfa59d2277",
+ "patch": [
+ "diff --git a/call-expressions.go b/call-expressions.go",
+ "index e69de29..ecd7132 100644",
+ "--- a/call-expressions.go",
+ "+++ b/call-expressions.go",
+ "@@ -0,0 +1,3 @@",
+ "+x(b, c...)",
+ "+y(b, c,)",
+ "+z(b,c...,)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b012b29236710a735f6e72762337573a759aa242"
+ "shas": "aa129cc05ef2a77358a80e1404c396003e3738af..d0c30ac0a0df53039a6798f7c3f5837ab95d4737"
}
,{
"testCaseDescription": "go-call-expressions-replacement-insert-test",
@@ -50,11 +167,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -65,11 +182,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -80,11 +197,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -95,11 +212,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -110,11 +227,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
4
]
}
@@ -125,11 +242,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -140,11 +257,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -155,11 +272,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
3
],
"end": [
- 5,
+ 3,
4
]
}
@@ -170,11 +287,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
6
]
}
@@ -185,11 +302,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -200,11 +317,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
3
],
"end": [
- 6,
+ 4,
4
]
}
@@ -215,11 +332,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -230,11 +347,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -245,11 +362,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
3
],
"end": [
- 7,
+ 5,
4
]
}
@@ -260,11 +377,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
6
],
"end": [
- 7,
+ 5,
7
]
}
@@ -275,11 +392,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -290,11 +407,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
3
],
"end": [
- 8,
+ 6,
4
]
}
@@ -305,11 +422,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
5
],
"end": [
- 8,
+ 6,
6
]
}
@@ -323,9 +440,24 @@
"filePaths": [
"call-expressions.go"
],
- "sha1": "b012b29236710a735f6e72762337573a759aa242",
+ "patch": [
+ "diff --git a/call-expressions.go b/call-expressions.go",
+ "index ecd7132..d979c0a 100644",
+ "--- a/call-expressions.go",
+ "+++ b/call-expressions.go",
+ "@@ -1,3 +1,9 @@",
+ "+a(b, c...)",
+ "+b(b, c,)",
+ "+c(b,c...,)",
+ "+x(b, c...)",
+ "+y(b, c,)",
+ "+z(b,c...,)",
+ " x(b, c...)",
+ " y(b, c,)",
+ " z(b,c...,)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "af9d11cc628384dfb084adb962cb7362967a11eb"
+ "shas": "d0c30ac0a0df53039a6798f7c3f5837ab95d4737..ae506be3dd152c0db1771926975d8b4050979800"
}
,{
"testCaseDescription": "go-call-expressions-delete-insert-test",
@@ -336,11 +468,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -351,11 +483,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -366,11 +498,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -381,11 +513,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -396,11 +528,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
4
]
}
@@ -411,11 +543,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -426,11 +558,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -441,11 +573,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
3
],
"end": [
- 5,
+ 3,
4
]
}
@@ -456,11 +588,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
6
]
}
@@ -471,11 +603,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -486,11 +618,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -501,11 +633,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -516,11 +648,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -531,11 +663,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
4
]
}
@@ -546,11 +678,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -561,11 +693,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -576,11 +708,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
3
],
"end": [
- 5,
+ 3,
4
]
}
@@ -591,11 +723,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
6
]
}
@@ -609,9 +741,24 @@
"filePaths": [
"call-expressions.go"
],
- "sha1": "af9d11cc628384dfb084adb962cb7362967a11eb",
+ "patch": [
+ "diff --git a/call-expressions.go b/call-expressions.go",
+ "index d979c0a..a3950ff 100644",
+ "--- a/call-expressions.go",
+ "+++ b/call-expressions.go",
+ "@@ -1,6 +1,6 @@",
+ "-a(b, c...)",
+ "-b(b, c,)",
+ "-c(b,c...,)",
+ "+x(b, c...)",
+ "+y(b, c,)",
+ "+z(b,c...,)",
+ " x(b, c...)",
+ " y(b, c,)",
+ " z(b,c...,)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "da43cd5263fadfb3a7721efadd94e2ec8eb6a565"
+ "shas": "ae506be3dd152c0db1771926975d8b4050979800..dc22eead81d68192423f8be6bcff0bd551ca519c"
}
,{
"testCaseDescription": "go-call-expressions-replacement-test",
@@ -622,11 +769,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -637,11 +784,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -652,11 +799,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -667,11 +814,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -682,11 +829,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
4
]
}
@@ -697,11 +844,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -712,11 +859,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -727,11 +874,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
3
],
"end": [
- 5,
+ 3,
4
]
}
@@ -742,11 +889,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
6
]
}
@@ -757,11 +904,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -772,11 +919,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -787,11 +934,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -802,11 +949,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -817,11 +964,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
4
]
}
@@ -832,11 +979,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -847,11 +994,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -862,11 +1009,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
3
],
"end": [
- 5,
+ 3,
4
]
}
@@ -877,11 +1024,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
6
]
}
@@ -895,9 +1042,24 @@
"filePaths": [
"call-expressions.go"
],
- "sha1": "da43cd5263fadfb3a7721efadd94e2ec8eb6a565",
+ "patch": [
+ "diff --git a/call-expressions.go b/call-expressions.go",
+ "index a3950ff..d979c0a 100644",
+ "--- a/call-expressions.go",
+ "+++ b/call-expressions.go",
+ "@@ -1,6 +1,6 @@",
+ "-x(b, c...)",
+ "-y(b, c,)",
+ "-z(b,c...,)",
+ "+a(b, c...)",
+ "+b(b, c,)",
+ "+c(b,c...,)",
+ " x(b, c...)",
+ " y(b, c,)",
+ " z(b,c...,)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "9078afc8ef67ea3b698abcd11b713fce7d554297"
+ "shas": "dc22eead81d68192423f8be6bcff0bd551ca519c..fe4e6256ff7e844c807512283f93d3bbc3577568"
}
,{
"testCaseDescription": "go-call-expressions-delete-replacement-test",
@@ -908,11 +1070,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -923,11 +1085,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -938,11 +1100,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -953,11 +1115,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -968,11 +1130,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
4
]
}
@@ -983,11 +1145,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -998,11 +1160,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -1013,11 +1175,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
3
],
"end": [
- 5,
+ 3,
4
]
}
@@ -1028,11 +1190,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
6
]
}
@@ -1043,11 +1205,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -1058,11 +1220,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
3
],
"end": [
- 6,
+ 4,
4
]
}
@@ -1073,11 +1235,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -1088,11 +1250,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -1103,11 +1265,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
3
],
"end": [
- 7,
+ 5,
4
]
}
@@ -1118,11 +1280,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
6
],
"end": [
- 7,
+ 5,
7
]
}
@@ -1133,11 +1295,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -1148,11 +1310,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
3
],
"end": [
- 8,
+ 6,
4
]
}
@@ -1163,11 +1325,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
5
],
"end": [
- 8,
+ 6,
6
]
}
@@ -1178,11 +1340,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -1193,11 +1355,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
3
],
"end": [
- 6,
+ 4,
4
]
}
@@ -1208,11 +1370,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -1223,11 +1385,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -1238,11 +1400,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
3
],
"end": [
- 7,
+ 5,
4
]
}
@@ -1253,11 +1415,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
6
],
"end": [
- 7,
+ 5,
7
]
}
@@ -1268,11 +1430,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -1283,11 +1445,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
3
],
"end": [
- 8,
+ 6,
4
]
}
@@ -1298,11 +1460,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
5
],
"end": [
- 8,
+ 6,
6
]
}
@@ -1316,9 +1478,27 @@
"filePaths": [
"call-expressions.go"
],
- "sha1": "9078afc8ef67ea3b698abcd11b713fce7d554297",
+ "patch": [
+ "diff --git a/call-expressions.go b/call-expressions.go",
+ "index d979c0a..589914d 100644",
+ "--- a/call-expressions.go",
+ "+++ b/call-expressions.go",
+ "@@ -1,9 +1,6 @@",
+ "-a(b, c...)",
+ "-b(b, c,)",
+ "-c(b,c...,)",
+ "-x(b, c...)",
+ "-y(b, c,)",
+ "-z(b,c...,)",
+ " x(b, c...)",
+ " y(b, c,)",
+ " z(b,c...,)",
+ "+a(b, c...)",
+ "+b(b, c,)",
+ "+c(b,c...,)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7e0a6ba44779783d4e780ffb49daba429f924ef7"
+ "shas": "fe4e6256ff7e844c807512283f93d3bbc3577568..dea400c383d7e6766f20de290658f9bf1150d4af"
}
,{
"testCaseDescription": "go-call-expressions-delete-test",
@@ -1329,11 +1509,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -1344,11 +1524,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -1359,11 +1539,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -1374,11 +1554,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -1389,11 +1569,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
4
]
}
@@ -1404,11 +1584,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -1419,11 +1599,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -1434,11 +1614,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
3
],
"end": [
- 5,
+ 3,
4
]
}
@@ -1449,11 +1629,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
6
]
}
@@ -1467,9 +1647,21 @@
"filePaths": [
"call-expressions.go"
],
- "sha1": "7e0a6ba44779783d4e780ffb49daba429f924ef7",
+ "patch": [
+ "diff --git a/call-expressions.go b/call-expressions.go",
+ "index 589914d..1dc566c 100644",
+ "--- a/call-expressions.go",
+ "+++ b/call-expressions.go",
+ "@@ -1,6 +1,3 @@",
+ "-x(b, c...)",
+ "-y(b, c,)",
+ "-z(b,c...,)",
+ " a(b, c...)",
+ " b(b, c,)",
+ " c(b,c...,)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "688bfe8b2eef8f7b3bd03e0bc622274ba2789c27"
+ "shas": "dea400c383d7e6766f20de290658f9bf1150d4af..77444b7a73f9e31f8914d39035eb689613e7f6a7"
}
,{
"testCaseDescription": "go-call-expressions-delete-rest-test",
@@ -1478,30 +1670,138 @@
"call-expressions.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 2
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 3
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 6
+ ],
+ "end": [
+ 1,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 6
+ ],
+ "end": [
+ 2,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
}
]
},
@@ -1510,7 +1810,16 @@
"filePaths": [
"call-expressions.go"
],
- "sha1": "688bfe8b2eef8f7b3bd03e0bc622274ba2789c27",
+ "patch": [
+ "diff --git a/call-expressions.go b/call-expressions.go",
+ "index 1dc566c..e69de29 100644",
+ "--- a/call-expressions.go",
+ "+++ b/call-expressions.go",
+ "@@ -1,3 +0,0 @@",
+ "-a(b, c...)",
+ "-b(b, c,)",
+ "-c(b,c...,)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "feb6123e4d38848977a42544b3bae6334aecf1e0"
+ "shas": "77444b7a73f9e31f8914d39035eb689613e7f6a7..67f60ac0f2697ef8db7d2d1dba1a0b6528d97d51"
}]
diff --git a/test/corpus/diff-summaries/go/channel-types.json b/test/corpus/diff-summaries/go/channel-types.json
index e3b5884d9..02c560e22 100644
--- a/test/corpus/diff-summaries/go/channel-types.json
+++ b/test/corpus/diff-summaries/go/channel-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
19
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
18
],
"end": [
- 5,
+ 3,
26
]
}
@@ -67,11 +67,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -82,11 +82,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
18
],
"end": [
- 6,
+ 4,
21
]
}
@@ -100,9 +100,20 @@
"filePaths": [
"channel-types.go"
],
- "sha1": "9b11035ae1a210fb170ae96625f8e899d4d25b2f",
+ "patch": [
+ "diff --git a/channel-types.go b/channel-types.go",
+ "index e69de29..bd7de07 100644",
+ "--- a/channel-types.go",
+ "+++ b/channel-types.go",
+ "@@ -0,0 +1,5 @@",
+ "+type (",
+ "+c1 chan<- chan int",
+ "+c2 chan<- chan<- struct{}",
+ "+c3 chan<- <-chan int",
+ "+)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "8c30bbbabdf0a00f54abe83dfd6b77d1b2d787ff"
+ "shas": "bf799eac39c8188d30ac10bed1218975e6ad803c..3c790d1f3b674b89aeab94fc978503f4e67957b1"
}
,{
"testCaseDescription": "go-channel-types-replacement-insert-test",
@@ -113,11 +124,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -128,11 +139,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
22
]
}
@@ -143,11 +154,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -158,11 +169,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
18
],
"end": [
- 5,
+ 3,
26
]
}
@@ -173,11 +184,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -188,11 +199,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
18
],
"end": [
- 6,
+ 4,
24
]
}
@@ -203,11 +214,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
3
]
}
@@ -218,11 +229,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
16
],
"end": [
- 9,
+ 7,
19
]
}
@@ -233,11 +244,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
1
],
"end": [
- 10,
+ 8,
3
]
}
@@ -248,11 +259,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
18
],
"end": [
- 10,
+ 8,
26
]
}
@@ -263,11 +274,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 11,
+ 9,
3
]
}
@@ -278,11 +289,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
18
],
"end": [
- 11,
+ 9,
21
]
}
@@ -296,9 +307,29 @@
"filePaths": [
"channel-types.go"
],
- "sha1": "8c30bbbabdf0a00f54abe83dfd6b77d1b2d787ff",
+ "patch": [
+ "diff --git a/channel-types.go b/channel-types.go",
+ "index bd7de07..df89eec 100644",
+ "--- a/channel-types.go",
+ "+++ b/channel-types.go",
+ "@@ -1,4 +1,14 @@",
+ " type (",
+ "+c2 chan<- chan string",
+ "+c3 chan<- chan<- struct{}",
+ "+c4 chan<- <-chan string",
+ "+)",
+ "+type (",
+ "+c1 chan<- chan int",
+ "+c2 chan<- chan<- struct{}",
+ "+c3 chan<- <-chan int",
+ "+)",
+ "+type (",
+ " c1 chan<- chan int",
+ " c2 chan<- chan<- struct{}",
+ " c3 chan<- <-chan int"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "35cafe0ed04849a79bdedd5b353f6fbd7a88dac9"
+ "shas": "3c790d1f3b674b89aeab94fc978503f4e67957b1..7cafbf3038f13f6d91df0af32d14740622844453"
}
,{
"testCaseDescription": "go-channel-types-delete-insert-test",
@@ -309,11 +340,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -324,11 +355,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
19
]
}
@@ -339,11 +370,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
18
],
"end": [
- 5,
+ 3,
26
]
}
@@ -354,11 +385,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
22
]
}
@@ -369,11 +400,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
18
],
"end": [
- 6,
+ 4,
21
]
}
@@ -384,11 +415,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
18
],
"end": [
- 5,
+ 3,
26
]
}
@@ -399,11 +430,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -414,11 +445,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
18
],
"end": [
- 6,
+ 4,
24
]
}
@@ -432,9 +463,25 @@
"filePaths": [
"channel-types.go"
],
- "sha1": "35cafe0ed04849a79bdedd5b353f6fbd7a88dac9",
+ "patch": [
+ "diff --git a/channel-types.go b/channel-types.go",
+ "index df89eec..de689af 100644",
+ "--- a/channel-types.go",
+ "+++ b/channel-types.go",
+ "@@ -1,7 +1,7 @@",
+ " type (",
+ "-c2 chan<- chan string",
+ "-c3 chan<- chan<- struct{}",
+ "-c4 chan<- <-chan string",
+ "+c1 chan<- chan int",
+ "+c2 chan<- chan<- struct{}",
+ "+c3 chan<- <-chan int",
+ " )",
+ " type (",
+ " c1 chan<- chan int"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "82f288212c7909c6441e319ec8b5f58f7d2b13df"
+ "shas": "7cafbf3038f13f6d91df0af32d14740622844453..2e51ae64a206d361f20d4fe495df6a444e86a9d1"
}
,{
"testCaseDescription": "go-channel-types-replacement-test",
@@ -446,21 +493,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
},
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -473,21 +520,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
19
]
},
{
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
22
]
}
@@ -500,21 +547,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
},
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -526,11 +573,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -541,11 +588,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
18
],
"end": [
- 6,
+ 4,
24
]
}
@@ -556,11 +603,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -571,11 +618,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
18
],
"end": [
- 6,
+ 4,
21
]
}
@@ -589,9 +636,25 @@
"filePaths": [
"channel-types.go"
],
- "sha1": "82f288212c7909c6441e319ec8b5f58f7d2b13df",
+ "patch": [
+ "diff --git a/channel-types.go b/channel-types.go",
+ "index de689af..df89eec 100644",
+ "--- a/channel-types.go",
+ "+++ b/channel-types.go",
+ "@@ -1,7 +1,7 @@",
+ " type (",
+ "-c1 chan<- chan int",
+ "-c2 chan<- chan<- struct{}",
+ "-c3 chan<- <-chan int",
+ "+c2 chan<- chan string",
+ "+c3 chan<- chan<- struct{}",
+ "+c4 chan<- <-chan string",
+ " )",
+ " type (",
+ " c1 chan<- chan int"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "0cdce2141640bff6f94b760ae4b4df1f39a536c0"
+ "shas": "2e51ae64a206d361f20d4fe495df6a444e86a9d1..667505534f5764c27bfdbf32f8cbe400847d6b7b"
}
,{
"testCaseDescription": "go-channel-types-delete-replacement-test",
@@ -602,11 +665,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -617,11 +680,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
22
]
}
@@ -632,11 +695,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -647,11 +710,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
18
],
"end": [
- 5,
+ 3,
26
]
}
@@ -662,11 +725,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -677,11 +740,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
18
],
"end": [
- 6,
+ 4,
24
]
}
@@ -692,11 +755,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
3
]
}
@@ -707,11 +770,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
16
],
"end": [
- 9,
+ 7,
19
]
}
@@ -722,11 +785,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
1
],
"end": [
- 10,
+ 8,
3
]
}
@@ -737,11 +800,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
18
],
"end": [
- 10,
+ 8,
26
]
}
@@ -752,11 +815,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 11,
+ 9,
3
]
}
@@ -767,11 +830,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
18
],
"end": [
- 11,
+ 9,
21
]
}
@@ -782,11 +845,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
3
]
}
@@ -797,11 +860,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
16
],
"end": [
- 9,
+ 7,
22
]
}
@@ -812,11 +875,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
1
],
"end": [
- 10,
+ 8,
3
]
}
@@ -827,11 +890,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
18
],
"end": [
- 10,
+ 8,
26
]
}
@@ -842,11 +905,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 11,
+ 9,
3
]
}
@@ -857,11 +920,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
18
],
"end": [
- 11,
+ 9,
24
]
}
@@ -875,9 +938,33 @@
"filePaths": [
"channel-types.go"
],
- "sha1": "0cdce2141640bff6f94b760ae4b4df1f39a536c0",
+ "patch": [
+ "diff --git a/channel-types.go b/channel-types.go",
+ "index df89eec..145001b 100644",
+ "--- a/channel-types.go",
+ "+++ b/channel-types.go",
+ "@@ -1,15 +1,10 @@",
+ " type (",
+ "-c2 chan<- chan string",
+ "-c3 chan<- chan<- struct{}",
+ "-c4 chan<- <-chan string",
+ "-)",
+ "-type (",
+ " c1 chan<- chan int",
+ " c2 chan<- chan<- struct{}",
+ " c3 chan<- <-chan int",
+ " )",
+ " type (",
+ "-c1 chan<- chan int",
+ "-c2 chan<- chan<- struct{}",
+ "-c3 chan<- <-chan int",
+ "+c2 chan<- chan string",
+ "+c3 chan<- chan<- struct{}",
+ "+c4 chan<- <-chan string",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "61f72625844ffa46f216f8f0daa13eeb4d2bb833"
+ "shas": "667505534f5764c27bfdbf32f8cbe400847d6b7b..a40b1e61a9206c2dea1f2b6ea782cad89a2e109b"
}
,{
"testCaseDescription": "go-channel-types-delete-test",
@@ -888,11 +975,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -903,11 +990,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
19
]
}
@@ -918,11 +1005,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -933,11 +1020,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
18
],
"end": [
- 5,
+ 3,
26
]
}
@@ -948,11 +1035,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -963,11 +1050,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
18
],
"end": [
- 6,
+ 4,
21
]
}
@@ -981,9 +1068,24 @@
"filePaths": [
"channel-types.go"
],
- "sha1": "61f72625844ffa46f216f8f0daa13eeb4d2bb833",
+ "patch": [
+ "diff --git a/channel-types.go b/channel-types.go",
+ "index 145001b..a3506d3 100644",
+ "--- a/channel-types.go",
+ "+++ b/channel-types.go",
+ "@@ -1,9 +1,4 @@",
+ " type (",
+ "-c1 chan<- chan int",
+ "-c2 chan<- chan<- struct{}",
+ "-c3 chan<- <-chan int",
+ "-)",
+ "-type (",
+ " c2 chan<- chan string",
+ " c3 chan<- chan<- struct{}",
+ " c4 chan<- <-chan string"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "81fd59e942433d422d96d68768f49b8a1c0367b7"
+ "shas": "a40b1e61a9206c2dea1f2b6ea782cad89a2e109b..1fe2f76a12c981c18e0f04ca0608171106c82e8e"
}
,{
"testCaseDescription": "go-channel-types-delete-rest-test",
@@ -994,11 +1096,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -1009,11 +1111,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
22
]
}
@@ -1024,11 +1126,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -1039,11 +1141,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
18
],
"end": [
- 5,
+ 3,
26
]
}
@@ -1054,11 +1156,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -1069,11 +1171,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
18
],
"end": [
- 6,
+ 4,
24
]
}
@@ -1087,7 +1189,18 @@
"filePaths": [
"channel-types.go"
],
- "sha1": "81fd59e942433d422d96d68768f49b8a1c0367b7",
+ "patch": [
+ "diff --git a/channel-types.go b/channel-types.go",
+ "index a3506d3..e69de29 100644",
+ "--- a/channel-types.go",
+ "+++ b/channel-types.go",
+ "@@ -1,5 +0,0 @@",
+ "-type (",
+ "-c2 chan<- chan string",
+ "-c3 chan<- chan<- struct{}",
+ "-c4 chan<- <-chan string",
+ "-)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "aaf85bbdfa8ebd0c5c6eb74df937ad3e46d6a51e"
+ "shas": "1fe2f76a12c981c18e0f04ca0608171106c82e8e..f7bf78dc6e8a6f8dc89e11e588e1661394381c0d"
}]
diff --git a/test/corpus/diff-summaries/go/const-declarations-with-types.json b/test/corpus/diff-summaries/go/const-declarations-with-types.json
index ae790f702..825669733 100644
--- a/test/corpus/diff-summaries/go/const-declarations-with-types.json
+++ b/test/corpus/diff-summaries/go/const-declarations-with-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
19
]
}
@@ -25,9 +25,16 @@
"filePaths": [
"const-declarations-with-types.go"
],
- "sha1": "c21d0b27e7c59d7774df63523503c3bc468e4b03",
+ "patch": [
+ "diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
+ "index e69de29..da3bfc4 100644",
+ "--- a/const-declarations-with-types.go",
+ "+++ b/const-declarations-with-types.go",
+ "@@ -0,0 +1 @@",
+ "+const zero int = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "037b01f87e93e196246e7510a572960226d334c2"
+ "shas": "7c6671fbbc34d7ffd6c48ceafe5d7cb701952070..583d971ed03f04fe46711e9e2954e1fd8967ed9f"
}
,{
"testCaseDescription": "go-const-declarations-with-types-replacement-insert-test",
@@ -38,11 +45,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
30
]
}
@@ -53,11 +60,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
30
]
}
@@ -68,11 +75,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
19
]
}
@@ -86,9 +93,18 @@
"filePaths": [
"const-declarations-with-types.go"
],
- "sha1": "037b01f87e93e196246e7510a572960226d334c2",
+ "patch": [
+ "diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
+ "index da3bfc4..86f010e 100644",
+ "--- a/const-declarations-with-types.go",
+ "+++ b/const-declarations-with-types.go",
+ "@@ -1 +1,3 @@",
+ "+const one, two uiint64 = 1, 2",
+ "+const zero int = 0",
+ " const zero int = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "6361df62903f4e062984bdc670ce10de3dde2f40"
+ "shas": "583d971ed03f04fe46711e9e2954e1fd8967ed9f..6524d42fc14ef16ee8b4182d5ca6aa3b40c0ef22"
}
,{
"testCaseDescription": "go-const-declarations-with-types-delete-insert-test",
@@ -100,64 +116,64 @@
"replace": [
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
10
]
},
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
11
]
}
]
},
- "summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero variable of the 'main' module"
+ "summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
26
],
"end": [
- 3,
+ 1,
27
]
},
{
"start": [
- 3,
+ 1,
18
],
"end": [
- 3,
+ 1,
19
]
}
]
},
- "summary": "Replaced '1' with '0' in the zero variable of the 'main' module"
+ "summary": "Replaced '1' with '0' in the zero variable"
},
{
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
30
]
}
@@ -171,9 +187,19 @@
"filePaths": [
"const-declarations-with-types.go"
],
- "sha1": "6361df62903f4e062984bdc670ce10de3dde2f40",
+ "patch": [
+ "diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
+ "index 86f010e..049ca7f 100644",
+ "--- a/const-declarations-with-types.go",
+ "+++ b/const-declarations-with-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-const one, two uiint64 = 1, 2",
+ "+const zero int = 0",
+ " const zero int = 0",
+ " const zero int = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a15739d174f2a8ca5ca6e7c06384933ef0c70f97"
+ "shas": "6524d42fc14ef16ee8b4182d5ca6aa3b40c0ef22..0ed9143e58bc31164f36886a75e832881432cc87"
}
,{
"testCaseDescription": "go-const-declarations-with-types-replacement-test",
@@ -185,64 +211,64 @@
"replace": [
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
11
]
},
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
10
]
}
]
},
- "summary": "Replaced the 'zero' identifier with the 'one' identifier in the one variable of the 'main' module"
+ "summary": "Replaced the 'zero' identifier with the 'one' identifier in the one variable"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
18
],
"end": [
- 3,
+ 1,
19
]
},
{
"start": [
- 3,
+ 1,
26
],
"end": [
- 3,
+ 1,
27
]
}
]
},
- "summary": "Replaced '0' with '1' in the one variable of the 'main' module"
+ "summary": "Replaced '0' with '1' in the one variable"
},
{
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
30
]
}
@@ -256,9 +282,19 @@
"filePaths": [
"const-declarations-with-types.go"
],
- "sha1": "a15739d174f2a8ca5ca6e7c06384933ef0c70f97",
+ "patch": [
+ "diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
+ "index 049ca7f..86f010e 100644",
+ "--- a/const-declarations-with-types.go",
+ "+++ b/const-declarations-with-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-const zero int = 0",
+ "+const one, two uiint64 = 1, 2",
+ " const zero int = 0",
+ " const zero int = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "8458f0603f7f4fc15b6252185d5e735a91c8e2a0"
+ "shas": "0ed9143e58bc31164f36886a75e832881432cc87..d9db413fa87de51e109abeb31a69d648fc8414c2"
}
,{
"testCaseDescription": "go-const-declarations-with-types-delete-replacement-test",
@@ -269,11 +305,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
30
]
}
@@ -284,11 +320,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
30
]
}
@@ -299,11 +335,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
19
]
}
@@ -314,11 +350,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
30
]
}
@@ -329,11 +365,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
30
]
}
@@ -347,9 +383,19 @@
"filePaths": [
"const-declarations-with-types.go"
],
- "sha1": "8458f0603f7f4fc15b6252185d5e735a91c8e2a0",
+ "patch": [
+ "diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
+ "index 86f010e..f035105 100644",
+ "--- a/const-declarations-with-types.go",
+ "+++ b/const-declarations-with-types.go",
+ "@@ -1,3 +1,2 @@",
+ "-const one, two uiint64 = 1, 2",
+ "-const zero int = 0",
+ " const zero int = 0",
+ "+const one, two uiint64 = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "6ceaa758df5e705335778d863e4a000325a7188f"
+ "shas": "d9db413fa87de51e109abeb31a69d648fc8414c2..5810cba229beabf124f6fbf9f8839bf6516cbfec"
}
,{
"testCaseDescription": "go-const-declarations-with-types-delete-test",
@@ -360,11 +406,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
19
]
}
@@ -378,9 +424,17 @@
"filePaths": [
"const-declarations-with-types.go"
],
- "sha1": "6ceaa758df5e705335778d863e4a000325a7188f",
+ "patch": [
+ "diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
+ "index f035105..716746a 100644",
+ "--- a/const-declarations-with-types.go",
+ "+++ b/const-declarations-with-types.go",
+ "@@ -1,2 +1 @@",
+ "-const zero int = 0",
+ " const one, two uiint64 = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "205fd6749a22e393f4c96d72095a7347b473d3d7"
+ "shas": "5810cba229beabf124f6fbf9f8839bf6516cbfec..6f46e936e458f9355d6a374e25288b94989076d6"
}
,{
"testCaseDescription": "go-const-declarations-with-types-delete-rest-test",
@@ -391,11 +445,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
30
]
}
@@ -406,11 +460,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
30
]
}
@@ -424,7 +478,14 @@
"filePaths": [
"const-declarations-with-types.go"
],
- "sha1": "205fd6749a22e393f4c96d72095a7347b473d3d7",
+ "patch": [
+ "diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
+ "index 716746a..e69de29 100644",
+ "--- a/const-declarations-with-types.go",
+ "+++ b/const-declarations-with-types.go",
+ "@@ -1 +0,0 @@",
+ "-const one, two uiint64 = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "45b551f3f778995db1cbc9c4f64fc2a76995f41e"
+ "shas": "6f46e936e458f9355d6a374e25288b94989076d6..95f53bbe92bd5841e140af869c4f35cb74379028"
}]
diff --git a/test/corpus/diff-summaries/go/const-declarations-without-types.json b/test/corpus/diff-summaries/go/const-declarations-without-types.json
index 5af5f844b..c0e367ffb 100644
--- a/test/corpus/diff-summaries/go/const-declarations-without-types.json
+++ b/test/corpus/diff-summaries/go/const-declarations-without-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
15
]
}
@@ -25,9 +25,16 @@
"filePaths": [
"const-declarations-without-types.go"
],
- "sha1": "f99392e84d40bc621fdc924228e731d179062c0b",
+ "patch": [
+ "diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
+ "index e69de29..2f2e175 100644",
+ "--- a/const-declarations-without-types.go",
+ "+++ b/const-declarations-without-types.go",
+ "@@ -0,0 +1 @@",
+ "+const zero = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "1aeedda828a7dda70f61221adf03427cd19ad270"
+ "shas": "47227a5c2dd60f353b45407e2d7695a53dc5bab9..c650e59013878fb76859603a33f695e9a42ab44d"
}
,{
"testCaseDescription": "go-const-declarations-without-types-replacement-insert-test",
@@ -38,11 +45,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -53,11 +60,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -68,11 +75,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
15
]
}
@@ -86,9 +93,18 @@
"filePaths": [
"const-declarations-without-types.go"
],
- "sha1": "1aeedda828a7dda70f61221adf03427cd19ad270",
+ "patch": [
+ "diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
+ "index 2f2e175..2d4a6fd 100644",
+ "--- a/const-declarations-without-types.go",
+ "+++ b/const-declarations-without-types.go",
+ "@@ -1 +1,3 @@",
+ "+const one, two = 1, 2",
+ "+const zero = 0",
+ " const zero = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "90d6f25afff0c53fc696d3d4a402e486b099effa"
+ "shas": "c650e59013878fb76859603a33f695e9a42ab44d..293c1186dbff3ce68dc45b31996c35d9b08017f2"
}
,{
"testCaseDescription": "go-const-declarations-without-types-delete-insert-test",
@@ -100,64 +116,64 @@
"replace": [
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
10
]
},
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
11
]
}
]
},
- "summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero variable of the 'main' module"
+ "summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
18
],
"end": [
- 3,
+ 1,
19
]
},
{
"start": [
- 3,
+ 1,
14
],
"end": [
- 3,
+ 1,
15
]
}
]
},
- "summary": "Replaced '1' with '0' in the zero variable of the 'main' module"
+ "summary": "Replaced '1' with '0' in the zero variable"
},
{
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -171,9 +187,19 @@
"filePaths": [
"const-declarations-without-types.go"
],
- "sha1": "90d6f25afff0c53fc696d3d4a402e486b099effa",
+ "patch": [
+ "diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
+ "index 2d4a6fd..b60f29e 100644",
+ "--- a/const-declarations-without-types.go",
+ "+++ b/const-declarations-without-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-const one, two = 1, 2",
+ "+const zero = 0",
+ " const zero = 0",
+ " const zero = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7808862de1745ca995adc4fa43c1a257f3c959bf"
+ "shas": "293c1186dbff3ce68dc45b31996c35d9b08017f2..fcf3cba3eb450ffbe0c7a99281a5f4cbcd0d60f4"
}
,{
"testCaseDescription": "go-const-declarations-without-types-replacement-test",
@@ -185,64 +211,64 @@
"replace": [
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
11
]
},
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
10
]
}
]
},
- "summary": "Replaced the 'zero' identifier with the 'one' identifier in the one variable of the 'main' module"
+ "summary": "Replaced the 'zero' identifier with the 'one' identifier in the one variable"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
14
],
"end": [
- 3,
+ 1,
15
]
},
{
"start": [
- 3,
+ 1,
18
],
"end": [
- 3,
+ 1,
19
]
}
]
},
- "summary": "Replaced '0' with '1' in the one variable of the 'main' module"
+ "summary": "Replaced '0' with '1' in the one variable"
},
{
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -256,9 +282,19 @@
"filePaths": [
"const-declarations-without-types.go"
],
- "sha1": "7808862de1745ca995adc4fa43c1a257f3c959bf",
+ "patch": [
+ "diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
+ "index b60f29e..2d4a6fd 100644",
+ "--- a/const-declarations-without-types.go",
+ "+++ b/const-declarations-without-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-const zero = 0",
+ "+const one, two = 1, 2",
+ " const zero = 0",
+ " const zero = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "624ed9b2234e961fd0c468233cb107b4e8c5dfa5"
+ "shas": "fcf3cba3eb450ffbe0c7a99281a5f4cbcd0d60f4..55a610329ed6c20c9bb7cc73e0490ce448a0cd5f"
}
,{
"testCaseDescription": "go-const-declarations-without-types-delete-replacement-test",
@@ -269,11 +305,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -284,11 +320,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -299,11 +335,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
15
]
}
@@ -314,11 +350,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
22
]
}
@@ -329,11 +365,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
22
]
}
@@ -347,9 +383,19 @@
"filePaths": [
"const-declarations-without-types.go"
],
- "sha1": "624ed9b2234e961fd0c468233cb107b4e8c5dfa5",
+ "patch": [
+ "diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
+ "index 2d4a6fd..0cb8229 100644",
+ "--- a/const-declarations-without-types.go",
+ "+++ b/const-declarations-without-types.go",
+ "@@ -1,3 +1,2 @@",
+ "-const one, two = 1, 2",
+ "-const zero = 0",
+ " const zero = 0",
+ "+const one, two = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "440cf2448c118a2373813a5fe19a96d558943dd1"
+ "shas": "55a610329ed6c20c9bb7cc73e0490ce448a0cd5f..fc5a942eccd22eaa8f7acca5b37460dd6c867dba"
}
,{
"testCaseDescription": "go-const-declarations-without-types-delete-test",
@@ -360,11 +406,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
15
]
}
@@ -378,9 +424,17 @@
"filePaths": [
"const-declarations-without-types.go"
],
- "sha1": "440cf2448c118a2373813a5fe19a96d558943dd1",
+ "patch": [
+ "diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
+ "index 0cb8229..83cc71f 100644",
+ "--- a/const-declarations-without-types.go",
+ "+++ b/const-declarations-without-types.go",
+ "@@ -1,2 +1 @@",
+ "-const zero = 0",
+ " const one, two = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "63236464b373c75b26318e339d0a64f9c37ab843"
+ "shas": "fc5a942eccd22eaa8f7acca5b37460dd6c867dba..3954838abc7833ed1cf3fec73b3d00436e14676a"
}
,{
"testCaseDescription": "go-const-declarations-without-types-delete-rest-test",
@@ -391,11 +445,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -406,11 +460,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -424,7 +478,14 @@
"filePaths": [
"const-declarations-without-types.go"
],
- "sha1": "63236464b373c75b26318e339d0a64f9c37ab843",
+ "patch": [
+ "diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
+ "index 83cc71f..e69de29 100644",
+ "--- a/const-declarations-without-types.go",
+ "+++ b/const-declarations-without-types.go",
+ "@@ -1 +0,0 @@",
+ "-const one, two = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c21d0b27e7c59d7774df63523503c3bc468e4b03"
+ "shas": "3954838abc7833ed1cf3fec73b3d00436e14676a..7c6671fbbc34d7ffd6c48ceafe5d7cb701952070"
}]
diff --git a/test/corpus/diff-summaries/go/const-with-implicit-values.json b/test/corpus/diff-summaries/go/const-with-implicit-values.json
index b963ce1ed..e33374422 100644
--- a/test/corpus/diff-summaries/go/const-with-implicit-values.json
+++ b/test/corpus/diff-summaries/go/const-with-implicit-values.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -55,9 +55,20 @@
"filePaths": [
"const-with-implicit-values.go"
],
- "sha1": "475deec198e080301901a65778b6e2ee6255ee60",
+ "patch": [
+ "diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
+ "index e69de29..938a571 100644",
+ "--- a/const-with-implicit-values.go",
+ "+++ b/const-with-implicit-values.go",
+ "@@ -0,0 +1,5 @@",
+ "+const (",
+ "+ zero = iota",
+ "+ one",
+ "+ two",
+ "+ )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ac39692dc8e60b73af4c24df31d58e96a8cf4ae4"
+ "shas": "479bb7390b5a93cd2d670d77d3ac6bf6c4169be4..deb921d5c92c5599bf92d3a73434561717cc51fb"
}
,{
"testCaseDescription": "go-const-with-implicit-values-replacement-insert-test",
@@ -68,11 +79,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -83,11 +94,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -98,11 +109,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -113,11 +124,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -128,11 +139,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -143,11 +154,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -161,9 +172,29 @@
"filePaths": [
"const-with-implicit-values.go"
],
- "sha1": "ac39692dc8e60b73af4c24df31d58e96a8cf4ae4",
+ "patch": [
+ "diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
+ "index 938a571..071b359 100644",
+ "--- a/const-with-implicit-values.go",
+ "+++ b/const-with-implicit-values.go",
+ "@@ -1,4 +1,14 @@",
+ " const (",
+ "+ a = iota",
+ "+ b",
+ "+ c",
+ "+ )",
+ "+const (",
+ "+ zero = iota",
+ "+ one",
+ "+ two",
+ "+ )",
+ "+const (",
+ " zero = iota",
+ " one",
+ " two"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "784d367a0e4ba45ac0659e22c03a3f34d3c5394c"
+ "shas": "deb921d5c92c5599bf92d3a73434561717cc51fb..845186fb5aa10cf909a91e344b0642b04c714c6e"
}
,{
"testCaseDescription": "go-const-with-implicit-values-delete-insert-test",
@@ -175,48 +206,48 @@
"replace": [
{
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
3
]
},
{
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
6
]
}
]
},
- "summary": "Replaced the 'a' identifier with the 'zero' identifier in the zero variable of the 'main' module"
+ "summary": "Replaced the 'a' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
},
{
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
5
]
}
@@ -229,21 +260,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
3
]
},
{
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
5
]
}
@@ -258,9 +289,25 @@
"filePaths": [
"const-with-implicit-values.go"
],
- "sha1": "784d367a0e4ba45ac0659e22c03a3f34d3c5394c",
+ "patch": [
+ "diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
+ "index 071b359..8a6d638 100644",
+ "--- a/const-with-implicit-values.go",
+ "+++ b/const-with-implicit-values.go",
+ "@@ -1,7 +1,7 @@",
+ " const (",
+ "- a = iota",
+ "- b",
+ "- c",
+ "+ zero = iota",
+ "+ one",
+ "+ two",
+ " )",
+ " const (",
+ " zero = iota"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "d6fea3f4d2a09fb831635228ffd52e4029a66690"
+ "shas": "845186fb5aa10cf909a91e344b0642b04c714c6e..7d478cd8b81e9bd6ceab2d831e67fe84c2e5302b"
}
,{
"testCaseDescription": "go-const-with-implicit-values-replacement-test",
@@ -272,48 +319,48 @@
"replace": [
{
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
6
]
},
{
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
3
]
}
]
},
- "summary": "Replaced the 'zero' identifier with the 'a' identifier in the a variable of the 'main' module"
+ "summary": "Replaced the 'zero' identifier with the 'a' identifier in the a variable"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
5
]
},
{
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -326,21 +373,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
5
]
},
{
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
3
]
}
@@ -355,9 +402,25 @@
"filePaths": [
"const-with-implicit-values.go"
],
- "sha1": "d6fea3f4d2a09fb831635228ffd52e4029a66690",
+ "patch": [
+ "diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
+ "index 8a6d638..071b359 100644",
+ "--- a/const-with-implicit-values.go",
+ "+++ b/const-with-implicit-values.go",
+ "@@ -1,7 +1,7 @@",
+ " const (",
+ "- zero = iota",
+ "- one",
+ "- two",
+ "+ a = iota",
+ "+ b",
+ "+ c",
+ " )",
+ " const (",
+ " zero = iota"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b4617614ee8c58faf89055b68cbcd640663208d3"
+ "shas": "7d478cd8b81e9bd6ceab2d831e67fe84c2e5302b..c7803f6793bf104045f60805ea29e82b1e15c8de"
}
,{
"testCaseDescription": "go-const-with-implicit-values-delete-replacement-test",
@@ -368,11 +431,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -383,11 +446,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -398,11 +461,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -413,11 +476,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -428,11 +491,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -443,11 +506,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -458,11 +521,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -473,11 +536,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -488,11 +551,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -506,9 +569,33 @@
"filePaths": [
"const-with-implicit-values.go"
],
- "sha1": "b4617614ee8c58faf89055b68cbcd640663208d3",
+ "patch": [
+ "diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
+ "index 071b359..ae8b277 100644",
+ "--- a/const-with-implicit-values.go",
+ "+++ b/const-with-implicit-values.go",
+ "@@ -1,15 +1,10 @@",
+ " const (",
+ "- a = iota",
+ "- b",
+ "- c",
+ "- )",
+ "-const (",
+ " zero = iota",
+ " one",
+ " two",
+ " )",
+ " const (",
+ "- zero = iota",
+ "- one",
+ "- two",
+ "+ a = iota",
+ "+ b",
+ "+ c",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "0c0cd503b0f4d88a94cbee4fa7ad2b973e8960ac"
+ "shas": "c7803f6793bf104045f60805ea29e82b1e15c8de..549397a8b29323bb63774a7e6e7c9cbe12e8d585"
}
,{
"testCaseDescription": "go-const-with-implicit-values-delete-test",
@@ -519,11 +606,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -534,11 +621,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -549,11 +636,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -567,9 +654,24 @@
"filePaths": [
"const-with-implicit-values.go"
],
- "sha1": "0c0cd503b0f4d88a94cbee4fa7ad2b973e8960ac",
+ "patch": [
+ "diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
+ "index ae8b277..dfb4fad 100644",
+ "--- a/const-with-implicit-values.go",
+ "+++ b/const-with-implicit-values.go",
+ "@@ -1,9 +1,4 @@",
+ " const (",
+ "- zero = iota",
+ "- one",
+ "- two",
+ "- )",
+ "-const (",
+ " a = iota",
+ " b",
+ " c"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "295241a104dec9ecba7fa69ba2012d53d4f88618"
+ "shas": "549397a8b29323bb63774a7e6e7c9cbe12e8d585..791136ead6293a07a456aeece9d8fca54919f160"
}
,{
"testCaseDescription": "go-const-with-implicit-values-delete-rest-test",
@@ -580,11 +682,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -595,11 +697,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -610,11 +712,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -628,7 +730,18 @@
"filePaths": [
"const-with-implicit-values.go"
],
- "sha1": "295241a104dec9ecba7fa69ba2012d53d4f88618",
+ "patch": [
+ "diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
+ "index dfb4fad..e69de29 100644",
+ "--- a/const-with-implicit-values.go",
+ "+++ b/const-with-implicit-values.go",
+ "@@ -1,5 +0,0 @@",
+ "-const (",
+ "- a = iota",
+ "- b",
+ "- c",
+ "- )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "bd92d81359528aecb248c2875d9cb620f555c9a7"
+ "shas": "791136ead6293a07a456aeece9d8fca54919f160..40bb3501528e6739138d99014546c14c14335b62"
}]
diff --git a/test/corpus/diff-summaries/go/constructors.json b/test/corpus/diff-summaries/go/constructors.json
index 646070aa0..0fc8f8e5f 100644
--- a/test/corpus/diff-summaries/go/constructors.json
+++ b/test/corpus/diff-summaries/go/constructors.json
@@ -5,30 +5,198 @@
"constructors.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 5
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'make' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 13
+ ],
+ "end": [
+ 1,
+ 16
+ ]
+ }
+ },
+ "summary": "Added the 'int' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'make' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 13
+ ],
+ "end": [
+ 2,
+ 16
+ ]
+ }
+ },
+ "summary": "Added the 'int' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 19
+ ],
+ "end": [
+ 2,
+ 22
+ ]
+ }
+ },
+ "summary": "Added the 'new' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 25
+ ],
+ "end": [
+ 2,
+ 28
+ ]
+ }
+ },
+ "summary": "Added the 'old' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'make' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 13
+ ],
+ "end": [
+ 3,
+ 16
+ ]
+ }
+ },
+ "summary": "Added the 'int' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 18
+ ],
+ "end": [
+ 3,
+ 19
+ ]
+ }
+ },
+ "summary": "Added the '5'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 21
+ ],
+ "end": [
+ 3,
+ 23
+ ]
+ }
+ },
+ "summary": "Added the '10'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 2
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'new' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 10
+ ],
+ "end": [
+ 4,
+ 16
+ ]
+ }
+ },
+ "summary": "Added the 'string' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 17
+ ],
+ "end": [
+ 4,
+ 23
+ ]
+ }
+ },
+ "summary": "Added the 'string' identifier"
}
]
},
@@ -37,9 +205,19 @@
"filePaths": [
"constructors.go"
],
- "sha1": "bd92d81359528aecb248c2875d9cb620f555c9a7",
+ "patch": [
+ "diff --git a/constructors.go b/constructors.go",
+ "index e69de29..51ab923 100644",
+ "--- a/constructors.go",
+ "+++ b/constructors.go",
+ "@@ -0,0 +1,4 @@",
+ "+make(chan<- int)",
+ "+make(chan<- int, (new - old))",
+ "+make(chan<- int, 5, 10)",
+ "+ new(map[string]string)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "28e7694e2ed814c4a791ab79b7d746b1a983e06b"
+ "shas": "40bb3501528e6739138d99014546c14c14335b62..acf3ab754be165fc30a19be5c0f8127dd759b980"
}
,{
"testCaseDescription": "go-constructors-replacement-insert-test",
@@ -50,11 +228,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
5
]
}
@@ -65,11 +243,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
19
]
}
@@ -80,11 +258,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
5
]
}
@@ -95,11 +273,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
13
],
"end": [
- 4,
+ 2,
19
]
}
@@ -110,11 +288,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
22
],
"end": [
- 4,
+ 2,
25
]
}
@@ -125,11 +303,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
28
],
"end": [
- 4,
+ 2,
31
]
}
@@ -140,11 +318,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
5
]
}
@@ -155,11 +333,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
13
],
"end": [
- 5,
+ 3,
19
]
}
@@ -170,11 +348,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
21
],
"end": [
- 5,
+ 3,
22
]
}
@@ -185,11 +363,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
24
],
"end": [
- 5,
+ 3,
26
]
}
@@ -200,11 +378,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
5
]
}
@@ -215,11 +393,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
10
],
"end": [
- 6,
+ 4,
13
]
}
@@ -230,11 +408,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
14
],
"end": [
- 6,
+ 4,
17
]
}
@@ -245,11 +423,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
5
]
}
@@ -260,11 +438,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
13
],
"end": [
- 7,
+ 5,
16
]
}
@@ -275,11 +453,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
5
]
}
@@ -290,11 +468,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
13
],
"end": [
- 8,
+ 6,
16
]
}
@@ -305,11 +483,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
19
],
"end": [
- 8,
+ 6,
22
]
}
@@ -320,11 +498,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
25
],
"end": [
- 8,
+ 6,
28
]
}
@@ -335,11 +513,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
5
]
}
@@ -350,11 +528,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
13
],
"end": [
- 9,
+ 7,
16
]
}
@@ -365,11 +543,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
18
],
"end": [
- 9,
+ 7,
19
]
}
@@ -380,11 +558,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
21
],
"end": [
- 9,
+ 7,
23
]
}
@@ -395,11 +573,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
2
],
"end": [
- 10,
+ 8,
5
]
}
@@ -410,11 +588,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
10
],
"end": [
- 10,
+ 8,
16
]
}
@@ -425,11 +603,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
17
],
"end": [
- 10,
+ 8,
23
]
}
@@ -443,15 +621,86 @@
"filePaths": [
"constructors.go"
],
- "sha1": "28e7694e2ed814c4a791ab79b7d746b1a983e06b",
+ "patch": [
+ "diff --git a/constructors.go b/constructors.go",
+ "index 51ab923..76b35ec 100644",
+ "--- a/constructors.go",
+ "+++ b/constructors.go",
+ "@@ -1,3 +1,11 @@",
+ "+make(chan<- string)",
+ "+make(chan<- string, (new - old))",
+ "+make(chan<- string, 7, 11)",
+ "+ new(map[int]int)",
+ "+make(chan<- int)",
+ "+make(chan<- int, (new - old))",
+ "+make(chan<- int, 5, 10)",
+ "+ new(map[string]string)",
+ " make(chan<- int)",
+ " make(chan<- int, (new - old))",
+ " make(chan<- int, 5, 10)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "1af6763f4db005cf511659eca65857d5d22f85f7"
+ "shas": "acf3ab754be165fc30a19be5c0f8127dd759b980..22f58c3aa2ae0f0aa7a590f6cbbca5604c1ff8b2"
}
,{
"testCaseDescription": "go-constructors-delete-insert-test",
"expectedResult": {
"changes": {
"constructors.go": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 13
+ ],
+ "end": [
+ 1,
+ 19
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 13
+ ],
+ "end": [
+ 1,
+ 16
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'string' identifier with the 'int' identifier"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 2,
+ 13
+ ],
+ "end": [
+ 2,
+ 19
+ ]
+ },
+ {
+ "start": [
+ 2,
+ 13
+ ],
+ "end": [
+ 2,
+ 16
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'string' identifier with the 'int' identifier"
+ },
{
"span": {
"replace": [
@@ -484,75 +733,21 @@
"replace": [
{
"start": [
- 4,
- 13
- ],
- "end": [
- 4,
- 19
- ]
- },
- {
- "start": [
- 4,
- 13
- ],
- "end": [
- 4,
- 16
- ]
- }
- ]
- },
- "summary": "Replaced the 'string' identifier with the 'int' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 5,
- 13
- ],
- "end": [
- 5,
- 19
- ]
- },
- {
- "start": [
- 5,
- 13
- ],
- "end": [
- 5,
- 16
- ]
- }
- ]
- },
- "summary": "Replaced the 'string' identifier with the 'int' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 5,
+ 3,
21
],
"end": [
- 5,
+ 3,
22
]
},
{
"start": [
- 5,
+ 3,
18
],
"end": [
- 5,
+ 3,
19
]
}
@@ -565,21 +760,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
24
],
"end": [
- 5,
+ 3,
26
]
},
{
"start": [
- 5,
+ 3,
21
],
"end": [
- 5,
+ 3,
23
]
}
@@ -592,21 +787,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
10
],
"end": [
- 6,
+ 4,
13
]
},
{
"start": [
- 6,
+ 4,
10
],
"end": [
- 6,
+ 4,
16
]
}
@@ -619,21 +814,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
14
],
"end": [
- 6,
+ 4,
17
]
},
{
"start": [
- 6,
+ 4,
17
],
"end": [
- 6,
+ 4,
23
]
}
@@ -648,15 +843,86 @@
"filePaths": [
"constructors.go"
],
- "sha1": "1af6763f4db005cf511659eca65857d5d22f85f7",
+ "patch": [
+ "diff --git a/constructors.go b/constructors.go",
+ "index 76b35ec..b8e9fef 100644",
+ "--- a/constructors.go",
+ "+++ b/constructors.go",
+ "@@ -1,7 +1,7 @@",
+ "-make(chan<- string)",
+ "-make(chan<- string, (new - old))",
+ "-make(chan<- string, 7, 11)",
+ "- new(map[int]int)",
+ "+make(chan<- int)",
+ "+make(chan<- int, (new - old))",
+ "+make(chan<- int, 5, 10)",
+ "+ new(map[string]string)",
+ " make(chan<- int)",
+ " make(chan<- int, (new - old))",
+ " make(chan<- int, 5, 10)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f10e80490d6efd6487856a7a6a06e50ce7a04b10"
+ "shas": "22f58c3aa2ae0f0aa7a590f6cbbca5604c1ff8b2..95d582455ca3332a68b8c7811bc98060f0f4679e"
}
,{
"testCaseDescription": "go-constructors-replacement-test",
"expectedResult": {
"changes": {
"constructors.go": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 13
+ ],
+ "end": [
+ 1,
+ 16
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 13
+ ],
+ "end": [
+ 1,
+ 19
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'int' identifier with the 'string' identifier"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 2,
+ 13
+ ],
+ "end": [
+ 2,
+ 16
+ ]
+ },
+ {
+ "start": [
+ 2,
+ 13
+ ],
+ "end": [
+ 2,
+ 19
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'int' identifier with the 'string' identifier"
+ },
{
"span": {
"replace": [
@@ -689,75 +955,21 @@
"replace": [
{
"start": [
- 4,
- 13
- ],
- "end": [
- 4,
- 16
- ]
- },
- {
- "start": [
- 4,
- 13
- ],
- "end": [
- 4,
- 19
- ]
- }
- ]
- },
- "summary": "Replaced the 'int' identifier with the 'string' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 5,
- 13
- ],
- "end": [
- 5,
- 16
- ]
- },
- {
- "start": [
- 5,
- 13
- ],
- "end": [
- 5,
- 19
- ]
- }
- ]
- },
- "summary": "Replaced the 'int' identifier with the 'string' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 5,
+ 3,
18
],
"end": [
- 5,
+ 3,
19
]
},
{
"start": [
- 5,
+ 3,
21
],
"end": [
- 5,
+ 3,
22
]
}
@@ -770,21 +982,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
21
],
"end": [
- 5,
+ 3,
23
]
},
{
"start": [
- 5,
+ 3,
24
],
"end": [
- 5,
+ 3,
26
]
}
@@ -797,21 +1009,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
10
],
"end": [
- 6,
+ 4,
16
]
},
{
"start": [
- 6,
+ 4,
10
],
"end": [
- 6,
+ 4,
13
]
}
@@ -824,21 +1036,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
17
],
"end": [
- 6,
+ 4,
23
]
},
{
"start": [
- 6,
+ 4,
14
],
"end": [
- 6,
+ 4,
17
]
}
@@ -853,9 +1065,26 @@
"filePaths": [
"constructors.go"
],
- "sha1": "f10e80490d6efd6487856a7a6a06e50ce7a04b10",
+ "patch": [
+ "diff --git a/constructors.go b/constructors.go",
+ "index b8e9fef..76b35ec 100644",
+ "--- a/constructors.go",
+ "+++ b/constructors.go",
+ "@@ -1,7 +1,7 @@",
+ "-make(chan<- int)",
+ "-make(chan<- int, (new - old))",
+ "-make(chan<- int, 5, 10)",
+ "- new(map[string]string)",
+ "+make(chan<- string)",
+ "+make(chan<- string, (new - old))",
+ "+make(chan<- string, 7, 11)",
+ "+ new(map[int]int)",
+ " make(chan<- int)",
+ " make(chan<- int, (new - old))",
+ " make(chan<- int, 5, 10)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "915978c743b9e63ed5aad01d1978eee2273916b1"
+ "shas": "95d582455ca3332a68b8c7811bc98060f0f4679e..966f8623aff6bab7254d116a94f55de562fa27b6"
}
,{
"testCaseDescription": "go-constructors-delete-replacement-test",
@@ -866,11 +1095,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
5
]
}
@@ -881,11 +1110,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
19
]
}
@@ -896,11 +1125,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
5
]
}
@@ -911,11 +1140,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
13
],
"end": [
- 4,
+ 2,
19
]
}
@@ -926,11 +1155,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
22
],
"end": [
- 4,
+ 2,
25
]
}
@@ -941,11 +1170,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
28
],
"end": [
- 4,
+ 2,
31
]
}
@@ -956,11 +1185,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
5
]
}
@@ -971,11 +1200,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
13
],
"end": [
- 5,
+ 3,
19
]
}
@@ -986,11 +1215,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
21
],
"end": [
- 5,
+ 3,
22
]
}
@@ -1001,11 +1230,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
24
],
"end": [
- 5,
+ 3,
26
]
}
@@ -1016,11 +1245,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
5
]
}
@@ -1031,11 +1260,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
10
],
"end": [
- 6,
+ 4,
13
]
}
@@ -1046,11 +1275,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
14
],
"end": [
- 6,
+ 4,
17
]
}
@@ -1061,11 +1290,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
5
]
}
@@ -1076,11 +1305,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
13
],
"end": [
- 7,
+ 5,
16
]
}
@@ -1091,11 +1320,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
5
]
}
@@ -1106,11 +1335,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
13
],
"end": [
- 8,
+ 6,
16
]
}
@@ -1121,11 +1350,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
19
],
"end": [
- 8,
+ 6,
22
]
}
@@ -1136,11 +1365,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
25
],
"end": [
- 8,
+ 6,
28
]
}
@@ -1151,11 +1380,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
5
]
}
@@ -1166,11 +1395,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
13
],
"end": [
- 9,
+ 7,
16
]
}
@@ -1181,11 +1410,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
18
],
"end": [
- 9,
+ 7,
19
]
}
@@ -1196,11 +1425,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
21
],
"end": [
- 9,
+ 7,
23
]
}
@@ -1211,11 +1440,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
2
],
"end": [
- 10,
+ 8,
5
]
}
@@ -1226,11 +1455,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
10
],
"end": [
- 10,
+ 8,
16
]
}
@@ -1241,11 +1470,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
17
],
"end": [
- 10,
+ 8,
23
]
}
@@ -1256,11 +1485,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
5
]
}
@@ -1271,11 +1500,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
13
],
"end": [
- 7,
+ 5,
19
]
}
@@ -1286,11 +1515,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
5
]
}
@@ -1301,11 +1530,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
13
],
"end": [
- 8,
+ 6,
19
]
}
@@ -1316,11 +1545,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
22
],
"end": [
- 8,
+ 6,
25
]
}
@@ -1331,11 +1560,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
28
],
"end": [
- 8,
+ 6,
31
]
}
@@ -1346,11 +1575,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
5
]
}
@@ -1361,11 +1590,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
13
],
"end": [
- 9,
+ 7,
19
]
}
@@ -1376,11 +1605,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
21
],
"end": [
- 9,
+ 7,
22
]
}
@@ -1391,11 +1620,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
24
],
"end": [
- 9,
+ 7,
26
]
}
@@ -1406,11 +1635,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
2
],
"end": [
- 10,
+ 8,
5
]
}
@@ -1421,11 +1650,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
10
],
"end": [
- 10,
+ 8,
13
]
}
@@ -1436,11 +1665,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
14
],
"end": [
- 10,
+ 8,
17
]
}
@@ -1454,9 +1683,31 @@
"filePaths": [
"constructors.go"
],
- "sha1": "915978c743b9e63ed5aad01d1978eee2273916b1",
+ "patch": [
+ "diff --git a/constructors.go b/constructors.go",
+ "index 76b35ec..12f44d5 100644",
+ "--- a/constructors.go",
+ "+++ b/constructors.go",
+ "@@ -1,12 +1,8 @@",
+ "-make(chan<- string)",
+ "-make(chan<- string, (new - old))",
+ "-make(chan<- string, 7, 11)",
+ "- new(map[int]int)",
+ "-make(chan<- int)",
+ "-make(chan<- int, (new - old))",
+ "-make(chan<- int, 5, 10)",
+ "- new(map[string]string)",
+ " make(chan<- int)",
+ " make(chan<- int, (new - old))",
+ " make(chan<- int, 5, 10)",
+ " new(map[string]string)",
+ "+make(chan<- string)",
+ "+make(chan<- string, (new - old))",
+ "+make(chan<- string, 7, 11)",
+ "+ new(map[int]int)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "35b0d9fbe6420dfde238c2f3e568e7641b97a504"
+ "shas": "966f8623aff6bab7254d116a94f55de562fa27b6..dcf2177ce94c3b563ca14e21f7ffa1e302dadc59"
}
,{
"testCaseDescription": "go-constructors-delete-test",
@@ -1467,11 +1718,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
5
]
}
@@ -1482,11 +1733,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
16
]
}
@@ -1497,11 +1748,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
5
]
}
@@ -1512,11 +1763,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
13
],
"end": [
- 4,
+ 2,
16
]
}
@@ -1527,11 +1778,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
19
],
"end": [
- 4,
+ 2,
22
]
}
@@ -1542,11 +1793,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
25
],
"end": [
- 4,
+ 2,
28
]
}
@@ -1557,11 +1808,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
5
]
}
@@ -1572,11 +1823,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
13
],
"end": [
- 5,
+ 3,
16
]
}
@@ -1587,11 +1838,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
18
],
"end": [
- 5,
+ 3,
19
]
}
@@ -1602,11 +1853,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
21
],
"end": [
- 5,
+ 3,
23
]
}
@@ -1617,11 +1868,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
5
]
}
@@ -1632,11 +1883,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
10
],
"end": [
- 6,
+ 4,
16
]
}
@@ -1647,11 +1898,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
17
],
"end": [
- 6,
+ 4,
23
]
}
@@ -1665,9 +1916,22 @@
"filePaths": [
"constructors.go"
],
- "sha1": "35b0d9fbe6420dfde238c2f3e568e7641b97a504",
+ "patch": [
+ "diff --git a/constructors.go b/constructors.go",
+ "index 12f44d5..0720537 100644",
+ "--- a/constructors.go",
+ "+++ b/constructors.go",
+ "@@ -1,7 +1,3 @@",
+ "-make(chan<- int)",
+ "-make(chan<- int, (new - old))",
+ "-make(chan<- int, 5, 10)",
+ "- new(map[string]string)",
+ " make(chan<- string)",
+ " make(chan<- string, (new - old))",
+ " make(chan<- string, 7, 11)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "11b3dd12241fa6607fa6f9116fce96f3f43aaa6a"
+ "shas": "dcf2177ce94c3b563ca14e21f7ffa1e302dadc59..b842d9b78fdf1ecc8ae0b611e736a4a0d7f272a2"
}
,{
"testCaseDescription": "go-constructors-delete-rest-test",
@@ -1676,30 +1940,198 @@
"constructors.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 5
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'make' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 13
+ ],
+ "end": [
+ 1,
+ 19
+ ]
+ }
+ },
+ "summary": "Deleted the 'string' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'make' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 13
+ ],
+ "end": [
+ 2,
+ 19
+ ]
+ }
+ },
+ "summary": "Deleted the 'string' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 22
+ ],
+ "end": [
+ 2,
+ 25
+ ]
+ }
+ },
+ "summary": "Deleted the 'new' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 28
+ ],
+ "end": [
+ 2,
+ 31
+ ]
+ }
+ },
+ "summary": "Deleted the 'old' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'make' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 13
+ ],
+ "end": [
+ 3,
+ 19
+ ]
+ }
+ },
+ "summary": "Deleted the 'string' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 21
+ ],
+ "end": [
+ 3,
+ 22
+ ]
+ }
+ },
+ "summary": "Deleted the '7'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 24
+ ],
+ "end": [
+ 3,
+ 26
+ ]
+ }
+ },
+ "summary": "Deleted the '11'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 2
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'new' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 10
+ ],
+ "end": [
+ 4,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 14
+ ],
+ "end": [
+ 4,
+ 17
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier"
}
]
},
@@ -1708,7 +2140,17 @@
"filePaths": [
"constructors.go"
],
- "sha1": "11b3dd12241fa6607fa6f9116fce96f3f43aaa6a",
+ "patch": [
+ "diff --git a/constructors.go b/constructors.go",
+ "index 0720537..e69de29 100644",
+ "--- a/constructors.go",
+ "+++ b/constructors.go",
+ "@@ -1,4 +0,0 @@",
+ "-make(chan<- string)",
+ "-make(chan<- string, (new - old))",
+ "-make(chan<- string, 7, 11)",
+ "- new(map[int]int)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "4f37802913bc6d0558da212b36497be55209c99b"
+ "shas": "b842d9b78fdf1ecc8ae0b611e736a4a0d7f272a2..bf82bf19d4c58176cb36d1c4e0cb934241bd5394"
}]
diff --git a/test/corpus/diff-summaries/go/float-literals.json b/test/corpus/diff-summaries/go/float-literals.json
index 64f86ebb3..db9b1ce20 100644
--- a/test/corpus/diff-summaries/go/float-literals.json
+++ b/test/corpus/diff-summaries/go/float-literals.json
@@ -5,30 +5,153 @@
"float-literals.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 3
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'f1' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 6
+ ],
+ "end": [
+ 1,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the '1.5' float_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'f2' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 6
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the '1.5e100' float_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'f3' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 6
+ ],
+ "end": [
+ 3,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the '1.5e+50' float_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'f4' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 6
+ ],
+ "end": [
+ 4,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the '1.5e-5' float_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'f5' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 6
+ ],
+ "end": [
+ 5,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the '.5e-50' float_literal"
}
]
},
@@ -37,9 +160,20 @@
"filePaths": [
"float-literals.go"
],
- "sha1": "c084d45f7de68c3a9328f11b1ff483ad5260f06e",
+ "patch": [
+ "diff --git a/float-literals.go b/float-literals.go",
+ "index e69de29..60df0eb 100644",
+ "--- a/float-literals.go",
+ "+++ b/float-literals.go",
+ "@@ -0,0 +1,5 @@",
+ "+f1 = 1.5",
+ "+f2 = 1.5e100",
+ "+f3 = 1.5e+50",
+ "+f4 = 1.5e-5",
+ "+f5 = .5e-50"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f310caab70056f6b1d32cbc622f02fd29ff41d0f"
+ "shas": "b3266e749035509bbbd882ef5e2d3ad93c3c60bf..eaea183385f9a2bdbd21e8becc6ba530f58fdf8d"
}
,{
"testCaseDescription": "go-float-literals-replacement-insert-test",
@@ -50,11 +184,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
3
]
}
@@ -65,11 +199,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
9
]
}
@@ -80,11 +214,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -95,11 +229,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
13
]
}
@@ -110,11 +244,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -125,11 +259,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
13
]
}
@@ -140,11 +274,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -155,11 +289,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
12
]
}
@@ -170,11 +304,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -185,11 +319,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
6
],
"end": [
- 7,
+ 5,
12
]
}
@@ -200,11 +334,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
3
]
}
@@ -215,11 +349,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
9
]
}
@@ -230,11 +364,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
3
]
}
@@ -245,11 +379,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
13
]
}
@@ -260,11 +394,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
1
],
"end": [
- 10,
+ 8,
3
]
}
@@ -275,11 +409,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
6
],
"end": [
- 10,
+ 8,
13
]
}
@@ -290,11 +424,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 11,
+ 9,
3
]
}
@@ -305,11 +439,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
6
],
"end": [
- 11,
+ 9,
12
]
}
@@ -320,11 +454,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -335,11 +469,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
6
],
"end": [
- 12,
+ 10,
12
]
}
@@ -353,9 +487,28 @@
"filePaths": [
"float-literals.go"
],
- "sha1": "f310caab70056f6b1d32cbc622f02fd29ff41d0f",
+ "patch": [
+ "diff --git a/float-literals.go b/float-literals.go",
+ "index 60df0eb..c0dd078 100644",
+ "--- a/float-literals.go",
+ "+++ b/float-literals.go",
+ "@@ -1,3 +1,13 @@",
+ "+f2 = 1.5",
+ "+f3 = 1.5e100",
+ "+f4 = 1.5e+50",
+ "+f5 = 1.5e-5",
+ "+f6 = .5e-50",
+ "+f1 = 1.5",
+ "+f2 = 1.5e100",
+ "+f3 = 1.5e+50",
+ "+f4 = 1.5e-5",
+ "+f5 = .5e-50",
+ " f1 = 1.5",
+ " f2 = 1.5e100",
+ " f3 = 1.5e+50"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "57abbc9c55c969e493026374f06c8c831b1cacfe"
+ "shas": "eaea183385f9a2bdbd21e8becc6ba530f58fdf8d..ba5057dd616f692d4464b99b4370e63caa67e911"
}
,{
"testCaseDescription": "go-float-literals-delete-insert-test",
@@ -366,11 +519,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
3
]
}
@@ -381,11 +534,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
9
]
}
@@ -397,21 +550,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
9
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
13
]
}
@@ -424,21 +577,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
13
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
13
]
}
@@ -450,11 +603,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -465,11 +618,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
12
]
}
@@ -480,11 +633,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -495,11 +648,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
6
],
"end": [
- 7,
+ 5,
12
]
}
@@ -510,11 +663,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -525,11 +678,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
13
]
}
@@ -540,11 +693,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -555,11 +708,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
12
]
}
@@ -570,11 +723,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -585,11 +738,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
6
],
"end": [
- 7,
+ 5,
12
]
}
@@ -603,9 +756,28 @@
"filePaths": [
"float-literals.go"
],
- "sha1": "57abbc9c55c969e493026374f06c8c831b1cacfe",
+ "patch": [
+ "diff --git a/float-literals.go b/float-literals.go",
+ "index c0dd078..1d76e74 100644",
+ "--- a/float-literals.go",
+ "+++ b/float-literals.go",
+ "@@ -1,8 +1,8 @@",
+ "-f2 = 1.5",
+ "-f3 = 1.5e100",
+ "-f4 = 1.5e+50",
+ "-f5 = 1.5e-5",
+ "-f6 = .5e-50",
+ "+f1 = 1.5",
+ "+f2 = 1.5e100",
+ "+f3 = 1.5e+50",
+ "+f4 = 1.5e-5",
+ "+f5 = .5e-50",
+ " f1 = 1.5",
+ " f2 = 1.5e100",
+ " f3 = 1.5e+50"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ecf1d3218722b21fee69a8d32db53667c6e14ecb"
+ "shas": "ba5057dd616f692d4464b99b4370e63caa67e911..48f68f74d3659d80350805ec800fcacbe9c613a0"
}
,{
"testCaseDescription": "go-float-literals-replacement-test",
@@ -616,11 +788,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
3
]
}
@@ -631,11 +803,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
9
]
}
@@ -646,11 +818,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -661,11 +833,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
13
]
}
@@ -676,11 +848,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -691,11 +863,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
13
]
}
@@ -706,11 +878,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -721,11 +893,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
12
]
}
@@ -736,11 +908,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -751,11 +923,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
6
],
"end": [
- 7,
+ 5,
12
]
}
@@ -766,11 +938,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
3
]
}
@@ -781,11 +953,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
9
]
}
@@ -796,11 +968,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -811,11 +983,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
13
]
}
@@ -826,11 +998,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -841,11 +1013,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
13
]
}
@@ -856,11 +1028,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -871,11 +1043,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
12
]
}
@@ -886,11 +1058,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -901,11 +1073,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
6
],
"end": [
- 7,
+ 5,
12
]
}
@@ -919,9 +1091,28 @@
"filePaths": [
"float-literals.go"
],
- "sha1": "ecf1d3218722b21fee69a8d32db53667c6e14ecb",
+ "patch": [
+ "diff --git a/float-literals.go b/float-literals.go",
+ "index 1d76e74..c0dd078 100644",
+ "--- a/float-literals.go",
+ "+++ b/float-literals.go",
+ "@@ -1,8 +1,8 @@",
+ "-f1 = 1.5",
+ "-f2 = 1.5e100",
+ "-f3 = 1.5e+50",
+ "-f4 = 1.5e-5",
+ "-f5 = .5e-50",
+ "+f2 = 1.5",
+ "+f3 = 1.5e100",
+ "+f4 = 1.5e+50",
+ "+f5 = 1.5e-5",
+ "+f6 = .5e-50",
+ " f1 = 1.5",
+ " f2 = 1.5e100",
+ " f3 = 1.5e+50"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "6cd18c32525b03613a648a9e8b6fe9a9a0a2403f"
+ "shas": "48f68f74d3659d80350805ec800fcacbe9c613a0..b168cf6365b206ba6a0843b853eee0427a351f1f"
}
,{
"testCaseDescription": "go-float-literals-delete-replacement-test",
@@ -932,11 +1123,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
3
]
}
@@ -947,11 +1138,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
9
]
}
@@ -962,11 +1153,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -977,11 +1168,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
13
]
}
@@ -992,11 +1183,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -1007,11 +1198,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
13
]
}
@@ -1022,11 +1213,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -1037,11 +1228,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
12
]
}
@@ -1052,11 +1243,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -1067,11 +1258,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
6
],
"end": [
- 7,
+ 5,
12
]
}
@@ -1082,11 +1273,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
3
]
}
@@ -1097,11 +1288,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
9
]
}
@@ -1112,11 +1303,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
3
]
}
@@ -1127,11 +1318,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
13
]
}
@@ -1142,11 +1333,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
1
],
"end": [
- 10,
+ 8,
3
]
}
@@ -1157,11 +1348,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
6
],
"end": [
- 10,
+ 8,
13
]
}
@@ -1172,11 +1363,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 11,
+ 9,
3
]
}
@@ -1187,11 +1378,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
6
],
"end": [
- 11,
+ 9,
12
]
}
@@ -1202,11 +1393,11 @@
"span": {
"delete": {
"start": [
- 12,
+ 10,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -1217,11 +1408,11 @@
"span": {
"delete": {
"start": [
- 12,
+ 10,
6
],
"end": [
- 12,
+ 10,
12
]
}
@@ -1232,11 +1423,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
3
]
}
@@ -1247,11 +1438,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
9
]
}
@@ -1262,11 +1453,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
3
]
}
@@ -1277,11 +1468,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
13
]
}
@@ -1292,11 +1483,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
1
],
"end": [
- 10,
+ 8,
3
]
}
@@ -1307,11 +1498,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
6
],
"end": [
- 10,
+ 8,
13
]
}
@@ -1322,11 +1513,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 11,
+ 9,
3
]
}
@@ -1337,11 +1528,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
6
],
"end": [
- 11,
+ 9,
12
]
}
@@ -1352,11 +1543,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
1
],
"end": [
- 12,
+ 10,
3
]
}
@@ -1367,11 +1558,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
6
],
"end": [
- 12,
+ 10,
12
]
}
@@ -1385,9 +1576,35 @@
"filePaths": [
"float-literals.go"
],
- "sha1": "6cd18c32525b03613a648a9e8b6fe9a9a0a2403f",
+ "patch": [
+ "diff --git a/float-literals.go b/float-literals.go",
+ "index c0dd078..2fc4057 100644",
+ "--- a/float-literals.go",
+ "+++ b/float-literals.go",
+ "@@ -1,15 +1,10 @@",
+ "-f2 = 1.5",
+ "-f3 = 1.5e100",
+ "-f4 = 1.5e+50",
+ "-f5 = 1.5e-5",
+ "-f6 = .5e-50",
+ "-f1 = 1.5",
+ "-f2 = 1.5e100",
+ "-f3 = 1.5e+50",
+ "-f4 = 1.5e-5",
+ "-f5 = .5e-50",
+ " f1 = 1.5",
+ " f2 = 1.5e100",
+ " f3 = 1.5e+50",
+ " f4 = 1.5e-5",
+ " f5 = .5e-50",
+ "+f2 = 1.5",
+ "+f3 = 1.5e100",
+ "+f4 = 1.5e+50",
+ "+f5 = 1.5e-5",
+ "+f6 = .5e-50"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a219356fb360c04d34e779b45a5341f7154838da"
+ "shas": "b168cf6365b206ba6a0843b853eee0427a351f1f..e22b86851565f53e0258b2da7a67433954167a61"
}
,{
"testCaseDescription": "go-float-literals-delete-test",
@@ -1398,11 +1615,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
3
]
}
@@ -1413,11 +1630,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
9
]
}
@@ -1428,11 +1645,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -1443,11 +1660,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
13
]
}
@@ -1458,11 +1675,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -1473,11 +1690,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
13
]
}
@@ -1488,11 +1705,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -1503,11 +1720,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
12
]
}
@@ -1518,11 +1735,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -1533,11 +1750,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
6
],
"end": [
- 7,
+ 5,
12
]
}
@@ -1551,9 +1768,23 @@
"filePaths": [
"float-literals.go"
],
- "sha1": "a219356fb360c04d34e779b45a5341f7154838da",
+ "patch": [
+ "diff --git a/float-literals.go b/float-literals.go",
+ "index 2fc4057..c99af8e 100644",
+ "--- a/float-literals.go",
+ "+++ b/float-literals.go",
+ "@@ -1,8 +1,3 @@",
+ "-f1 = 1.5",
+ "-f2 = 1.5e100",
+ "-f3 = 1.5e+50",
+ "-f4 = 1.5e-5",
+ "-f5 = .5e-50",
+ " f2 = 1.5",
+ " f3 = 1.5e100",
+ " f4 = 1.5e+50"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "825a1f729314e06f2147be47074ab4b0bd5809a6"
+ "shas": "e22b86851565f53e0258b2da7a67433954167a61..18407d91f85464e0cc04d8492189646a1642450d"
}
,{
"testCaseDescription": "go-float-literals-delete-rest-test",
@@ -1562,30 +1793,153 @@
"float-literals.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 3
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'f2' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 6
+ ],
+ "end": [
+ 1,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the '1.5' float_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'f3' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 6
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the '1.5e100' float_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'f4' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 6
+ ],
+ "end": [
+ 3,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the '1.5e+50' float_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'f5' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 6
+ ],
+ "end": [
+ 4,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the '1.5e-5' float_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'f6' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 6
+ ],
+ "end": [
+ 5,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the '.5e-50' float_literal"
}
]
},
@@ -1594,7 +1948,18 @@
"filePaths": [
"float-literals.go"
],
- "sha1": "825a1f729314e06f2147be47074ab4b0bd5809a6",
+ "patch": [
+ "diff --git a/float-literals.go b/float-literals.go",
+ "index c99af8e..e69de29 100644",
+ "--- a/float-literals.go",
+ "+++ b/float-literals.go",
+ "@@ -1,5 +0,0 @@",
+ "-f2 = 1.5",
+ "-f3 = 1.5e100",
+ "-f4 = 1.5e+50",
+ "-f5 = 1.5e-5",
+ "-f6 = .5e-50"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a70b7582c8f3a84eac215e17fbe07868510577b3"
+ "shas": "18407d91f85464e0cc04d8492189646a1642450d..c39ed98d50a7d8637ad13d6581d0d0d6a4bd083d"
}]
diff --git a/test/corpus/diff-summaries/go/for-statements.json b/test/corpus/diff-summaries/go/for-statements.json
index 894f0100a..36fc17031 100644
--- a/test/corpus/diff-summaries/go/for-statements.json
+++ b/test/corpus/diff-summaries/go/for-statements.json
@@ -1,48 +1,5 @@
[{
"testCaseDescription": "go-for-statements-insert-test",
- "expectedResult": {
- "changes": {
- "for-statements.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
- },
- "summary": "Replaced the 'main' module with the 'main' module"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "for-statements.go"
- ],
- "sha1": "150f53c8cfb31186993a9588c913d8bcad3cef1d",
- "gitDir": "test/corpus/repos/go",
- "sha2": "21ac6fd6aef52591595b45a382ab3fbf4e5da753"
-}
-,{
- "testCaseDescription": "go-for-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"for-statements.go": [
@@ -50,86 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
2
],
"end": [
- 6,
- 2
- ]
- }
- },
- "summary": "Added the 'for ;; {\na()\ngoto loop\n}' for statement"
- },
- {
- "span": {
- "insert": {
- "start": [
- 7,
- 1
- ],
- "end": [
- 10,
- 2
- ]
- }
- },
- "summary": "Added the 'x := range y' for statement"
- },
- {
- "span": {
- "insert": {
- "start": [
- 11,
- 1
- ],
- "end": [
- 14,
- 2
- ]
- }
- },
- "summary": "Added the 'for ;; {\na()\ncontinue loop2\n}' for statement"
- },
- {
- "span": {
- "insert": {
- "start": [
- 15,
- 1
- ],
- "end": [
- 18,
- 2
- ]
- }
- },
- "summary": "Added the 'i < 10; i++' for statement"
- },
- {
- "span": {
- "insert": {
- "start": [
- 19,
- 1
- ],
- "end": [
- 22,
- 2
- ]
- }
- },
- "summary": "Added the 'for {\na(x)\nbreak\n}' for statement"
- },
- {
- "span": {
- "insert": {
- "start": [
- 23,
- 2
- ],
- "end": [
- 26,
+ 4,
2
]
}
@@ -140,11 +22,11 @@
"span": {
"insert": {
"start": [
- 27,
+ 5,
1
],
"end": [
- 30,
+ 8,
2
]
}
@@ -155,11 +37,11 @@
"span": {
"insert": {
"start": [
- 31,
+ 9,
1
],
"end": [
- 34,
+ 12,
2
]
}
@@ -170,11 +52,11 @@
"span": {
"insert": {
"start": [
- 35,
+ 13,
1
],
"end": [
- 38,
+ 16,
2
]
}
@@ -185,11 +67,11 @@
"span": {
"insert": {
"start": [
- 39,
+ 17,
1
],
"end": [
- 42,
+ 20,
2
]
}
@@ -203,12 +85,38 @@
"filePaths": [
"for-statements.go"
],
- "sha1": "21ac6fd6aef52591595b45a382ab3fbf4e5da753",
+ "patch": [
+ "diff --git a/for-statements.go b/for-statements.go",
+ "index e69de29..cf40a00 100644",
+ "--- a/for-statements.go",
+ "+++ b/for-statements.go",
+ "@@ -0,0 +1,20 @@",
+ "+ for {",
+ "+a()",
+ "+goto loop",
+ "+}",
+ "+for i := 0; i < 5; i++ {",
+ "+a()",
+ "+break loop",
+ "+}",
+ "+for ; i < 10; i++ {",
+ "+a()",
+ "+continue loop2",
+ "+}",
+ "+for ;; {",
+ "+a()",
+ "+continue",
+ "+}",
+ "+for x := range y {",
+ "+a(x)",
+ "+break",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e399c20d6dcbdd06e621ba91c2524985229c3f42"
+ "shas": "ca9ffb9a8bca75e34a2383f7d503d3b21d7b08cc..50e0a6df9a7ab1397bd3134f0eefb45dd0704f37"
}
,{
- "testCaseDescription": "go-for-statements-delete-insert-test",
+ "testCaseDescription": "go-for-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"for-statements.go": [
@@ -216,26 +124,56 @@
"span": {
"insert": {
"start": [
- 7,
- 1
+ 1,
+ 2
],
"end": [
- 10,
+ 4,
2
]
}
},
- "summary": "Added the 'i := 0; i < 5; i++' for statement"
+ "summary": "Added the 'for ;; {\na()\ngoto loop\n}' for statement"
},
{
"span": {
"insert": {
"start": [
- 11,
+ 5,
1
],
"end": [
- 14,
+ 8,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'x := range y' for statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 1
+ ],
+ "end": [
+ 12,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'for ;; {\na()\ncontinue loop2\n}' for statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 13,
+ 1
+ ],
+ "end": [
+ 16,
2
]
}
@@ -246,11 +184,196 @@
"span": {
"insert": {
"start": [
- 15,
+ 17,
1
],
"end": [
- 18,
+ 20,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'for {\na(x)\nbreak\n}' for statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 21,
+ 2
+ ],
+ "end": [
+ 24,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'for {\na()\ngoto loop\n}' for statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 25,
+ 1
+ ],
+ "end": [
+ 28,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'i := 0; i < 5; i++' for statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 29,
+ 1
+ ],
+ "end": [
+ 32,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'i < 10; i++' for statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 33,
+ 1
+ ],
+ "end": [
+ 36,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'for ;; {\na()\ncontinue\n}' for statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 37,
+ 1
+ ],
+ "end": [
+ 40,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'x := range y' for statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "for-statements.go"
+ ],
+ "patch": [
+ "diff --git a/for-statements.go b/for-statements.go",
+ "index cf40a00..4fd7ac5 100644",
+ "--- a/for-statements.go",
+ "+++ b/for-statements.go",
+ "@@ -1,3 +1,43 @@",
+ "+ for ;; {",
+ "+a()",
+ "+goto loop",
+ "+}",
+ "+for x := range y {",
+ "+a()",
+ "+break loop",
+ "+}",
+ "+for ;; {",
+ "+a()",
+ "+continue loop2",
+ "+}",
+ "+for ; i < 10; i++ {",
+ "+a()",
+ "+continue",
+ "+}",
+ "+for {",
+ "+a(x)",
+ "+break",
+ "+}",
+ "+ for {",
+ "+a()",
+ "+goto loop",
+ "+}",
+ "+for i := 0; i < 5; i++ {",
+ "+a()",
+ "+break loop",
+ "+}",
+ "+for ; i < 10; i++ {",
+ "+a()",
+ "+continue loop2",
+ "+}",
+ "+for ;; {",
+ "+a()",
+ "+continue",
+ "+}",
+ "+for x := range y {",
+ "+a(x)",
+ "+break",
+ "+}",
+ " for {",
+ " a()",
+ " goto loop"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "50e0a6df9a7ab1397bd3134f0eefb45dd0704f37..75845b55d73d133b7257cd14340d3d76cb3f1011"
+}
+,{
+ "testCaseDescription": "go-for-statements-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "for-statements.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 8,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'i := 0; i < 5; i++' for statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 1
+ ],
+ "end": [
+ 12,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'i < 10; i++' for statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 13,
+ 1
+ ],
+ "end": [
+ 16,
2
]
}
@@ -262,21 +385,21 @@
"replace": [
{
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
4
]
},
{
"start": [
- 20,
+ 18,
1
],
"end": [
- 20,
+ 18,
2
]
}
@@ -289,21 +412,21 @@
"replace": [
{
"start": [
- 9,
+ 7,
7
],
"end": [
- 9,
+ 7,
11
]
},
{
"start": [
- 21,
+ 19,
1
],
"end": [
- 21,
+ 19,
6
]
}
@@ -315,11 +438,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 14,
+ 12,
2
]
}
@@ -330,11 +453,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
1
],
"end": [
- 18,
+ 16,
2
]
}
@@ -345,11 +468,11 @@
"span": {
"delete": {
"start": [
- 19,
+ 17,
1
],
"end": [
- 22,
+ 20,
2
]
}
@@ -363,9 +486,40 @@
"filePaths": [
"for-statements.go"
],
- "sha1": "e399c20d6dcbdd06e621ba91c2524985229c3f42",
+ "patch": [
+ "diff --git a/for-statements.go b/for-statements.go",
+ "index 4fd7ac5..ac76ef3 100644",
+ "--- a/for-statements.go",
+ "+++ b/for-statements.go",
+ "@@ -1,20 +1,20 @@",
+ "- for ;; {",
+ "+ for {",
+ " a()",
+ " goto loop",
+ " }",
+ "-for x := range y {",
+ "+for i := 0; i < 5; i++ {",
+ " a()",
+ " break loop",
+ " }",
+ "-for ;; {",
+ "+for ; i < 10; i++ {",
+ " a()",
+ " continue loop2",
+ " }",
+ "-for ; i < 10; i++ {",
+ "+for ;; {",
+ " a()",
+ " continue",
+ " }",
+ "-for {",
+ "+for x := range y {",
+ " a(x)",
+ " break",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "da9601af0446030e832c0f250e004c135eb5f47e"
+ "shas": "75845b55d73d133b7257cd14340d3d76cb3f1011..cfc21bc775eca1f8281e9fcef32641941086ec88"
}
,{
"testCaseDescription": "go-for-statements-replacement-test",
@@ -376,11 +530,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -391,11 +545,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 14,
+ 12,
2
]
}
@@ -406,11 +560,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
1
],
"end": [
- 18,
+ 16,
2
]
}
@@ -421,11 +575,11 @@
"span": {
"insert": {
"start": [
- 19,
+ 17,
1
],
"end": [
- 22,
+ 20,
2
]
}
@@ -436,11 +590,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -451,11 +605,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 14,
+ 12,
2
]
}
@@ -466,11 +620,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
1
],
"end": [
- 18,
+ 16,
2
]
}
@@ -481,11 +635,11 @@
"span": {
"delete": {
"start": [
- 19,
+ 17,
1
],
"end": [
- 22,
+ 20,
2
]
}
@@ -499,9 +653,40 @@
"filePaths": [
"for-statements.go"
],
- "sha1": "da9601af0446030e832c0f250e004c135eb5f47e",
+ "patch": [
+ "diff --git a/for-statements.go b/for-statements.go",
+ "index ac76ef3..4fd7ac5 100644",
+ "--- a/for-statements.go",
+ "+++ b/for-statements.go",
+ "@@ -1,20 +1,20 @@",
+ "- for {",
+ "+ for ;; {",
+ " a()",
+ " goto loop",
+ " }",
+ "-for i := 0; i < 5; i++ {",
+ "+for x := range y {",
+ " a()",
+ " break loop",
+ " }",
+ "-for ; i < 10; i++ {",
+ "+for ;; {",
+ " a()",
+ " continue loop2",
+ " }",
+ "-for ;; {",
+ "+for ; i < 10; i++ {",
+ " a()",
+ " continue",
+ " }",
+ "-for x := range y {",
+ "+for {",
+ " a(x)",
+ " break",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "eb6fc97aa06a82c1a8c4e7706eb9e5aae065179e"
+ "shas": "cfc21bc775eca1f8281e9fcef32641941086ec88..3a95c2458393f4b7f5ab711b62e22371fbddd11d"
}
,{
"testCaseDescription": "go-for-statements-delete-replacement-test",
@@ -512,11 +697,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
2
],
"end": [
- 6,
+ 4,
2
]
}
@@ -527,11 +712,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -542,11 +727,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 14,
+ 12,
2
]
}
@@ -557,11 +742,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
1
],
"end": [
- 18,
+ 16,
2
]
}
@@ -572,11 +757,11 @@
"span": {
"delete": {
"start": [
- 19,
+ 17,
1
],
"end": [
- 22,
+ 20,
2
]
}
@@ -587,11 +772,11 @@
"span": {
"insert": {
"start": [
- 27,
+ 25,
1
],
"end": [
- 30,
+ 28,
2
]
}
@@ -602,11 +787,11 @@
"span": {
"insert": {
"start": [
- 31,
+ 29,
1
],
"end": [
- 34,
+ 32,
2
]
}
@@ -617,11 +802,11 @@
"span": {
"insert": {
"start": [
- 35,
+ 33,
1
],
"end": [
- 38,
+ 36,
2
]
}
@@ -632,11 +817,11 @@
"span": {
"insert": {
"start": [
- 39,
+ 37,
1
],
"end": [
- 42,
+ 40,
2
]
}
@@ -647,11 +832,11 @@
"span": {
"delete": {
"start": [
- 47,
+ 45,
1
],
"end": [
- 50,
+ 48,
2
]
}
@@ -662,11 +847,11 @@
"span": {
"delete": {
"start": [
- 51,
+ 49,
1
],
"end": [
- 54,
+ 52,
2
]
}
@@ -677,11 +862,11 @@
"span": {
"delete": {
"start": [
- 55,
+ 53,
1
],
"end": [
- 58,
+ 56,
2
]
}
@@ -692,11 +877,11 @@
"span": {
"delete": {
"start": [
- 59,
+ 57,
1
],
"end": [
- 62,
+ 60,
2
]
}
@@ -710,9 +895,67 @@
"filePaths": [
"for-statements.go"
],
- "sha1": "eb6fc97aa06a82c1a8c4e7706eb9e5aae065179e",
+ "patch": [
+ "diff --git a/for-statements.go b/for-statements.go",
+ "index 4fd7ac5..53849f8 100644",
+ "--- a/for-statements.go",
+ "+++ b/for-statements.go",
+ "@@ -1,23 +1,3 @@",
+ "- for ;; {",
+ "-a()",
+ "-goto loop",
+ "-}",
+ "-for x := range y {",
+ "-a()",
+ "-break loop",
+ "-}",
+ "-for ;; {",
+ "-a()",
+ "-continue loop2",
+ "-}",
+ "-for ; i < 10; i++ {",
+ "-a()",
+ "-continue",
+ "-}",
+ "-for {",
+ "-a(x)",
+ "-break",
+ "-}",
+ " for {",
+ " a()",
+ " goto loop",
+ "@@ -38,23 +18,23 @@ for x := range y {",
+ " a(x)",
+ " break",
+ " }",
+ "- for {",
+ "+ for ;; {",
+ " a()",
+ " goto loop",
+ " }",
+ "-for i := 0; i < 5; i++ {",
+ "+for x := range y {",
+ " a()",
+ " break loop",
+ " }",
+ "-for ; i < 10; i++ {",
+ "+for ;; {",
+ " a()",
+ " continue loop2",
+ " }",
+ "-for ;; {",
+ "+for ; i < 10; i++ {",
+ " a()",
+ " continue",
+ " }",
+ "-for x := range y {",
+ "+for {",
+ " a(x)",
+ " break",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7b11abfad6e1feb091a1e4ef17ac950317e10f3d"
+ "shas": "3a95c2458393f4b7f5ab711b62e22371fbddd11d..8435f02e02c478569822e353e06af4d8ac894751"
}
,{
"testCaseDescription": "go-for-statements-delete-test",
@@ -723,11 +966,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
2
],
"end": [
- 6,
+ 4,
2
]
}
@@ -738,11 +981,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -753,11 +996,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 14,
+ 12,
2
]
}
@@ -768,11 +1011,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
1
],
"end": [
- 18,
+ 16,
2
]
}
@@ -783,11 +1026,11 @@
"span": {
"delete": {
"start": [
- 19,
+ 17,
1
],
"end": [
- 22,
+ 20,
2
]
}
@@ -801,9 +1044,38 @@
"filePaths": [
"for-statements.go"
],
- "sha1": "7b11abfad6e1feb091a1e4ef17ac950317e10f3d",
+ "patch": [
+ "diff --git a/for-statements.go b/for-statements.go",
+ "index 53849f8..c242f13 100644",
+ "--- a/for-statements.go",
+ "+++ b/for-statements.go",
+ "@@ -1,23 +1,3 @@",
+ "- for {",
+ "-a()",
+ "-goto loop",
+ "-}",
+ "-for i := 0; i < 5; i++ {",
+ "-a()",
+ "-break loop",
+ "-}",
+ "-for ; i < 10; i++ {",
+ "-a()",
+ "-continue loop2",
+ "-}",
+ "-for ;; {",
+ "-a()",
+ "-continue",
+ "-}",
+ "-for x := range y {",
+ "-a(x)",
+ "-break",
+ "-}",
+ " for ;; {",
+ " a()",
+ " goto loop"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e610b3e454426cc74c7e50dea1796a8bc38028c3"
+ "shas": "8435f02e02c478569822e353e06af4d8ac894751..16022407f09de24425959f7b36c7710231a372c5"
}
,{
"testCaseDescription": "go-for-statements-delete-rest-test",
@@ -812,30 +1084,78 @@
"for-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 2
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'for ;; {\na()\ngoto loop\n}' for statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 8,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'x := range y' for statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 9,
+ 1
+ ],
+ "end": [
+ 12,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'for ;; {\na()\ncontinue loop2\n}' for statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 13,
+ 1
+ ],
+ "end": [
+ 16,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'i < 10; i++' for statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 17,
+ 1
+ ],
+ "end": [
+ 20,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'for {\na(x)\nbreak\n}' for statement"
}
]
},
@@ -844,7 +1164,33 @@
"filePaths": [
"for-statements.go"
],
- "sha1": "e610b3e454426cc74c7e50dea1796a8bc38028c3",
+ "patch": [
+ "diff --git a/for-statements.go b/for-statements.go",
+ "index c242f13..e69de29 100644",
+ "--- a/for-statements.go",
+ "+++ b/for-statements.go",
+ "@@ -1,20 +0,0 @@",
+ "- for ;; {",
+ "-a()",
+ "-goto loop",
+ "-}",
+ "-for x := range y {",
+ "-a()",
+ "-break loop",
+ "-}",
+ "-for ;; {",
+ "-a()",
+ "-continue loop2",
+ "-}",
+ "-for ; i < 10; i++ {",
+ "-a()",
+ "-continue",
+ "-}",
+ "-for {",
+ "-a(x)",
+ "-break",
+ "-}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e16450a4f5054f826123def384b72eb4946a4544"
+ "shas": "16022407f09de24425959f7b36c7710231a372c5..26a36f6042d04bfd0685dc779d24c8601a19a4ce"
}]
diff --git a/test/corpus/diff-summaries/go/function-declarations.json b/test/corpus/diff-summaries/go/function-declarations.json
index 66fa05f84..5435f64ee 100644
--- a/test/corpus/diff-summaries/go/function-declarations.json
+++ b/test/corpus/diff-summaries/go/function-declarations.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
11
],
"end": [
- 4,
+ 2,
14
]
}
@@ -67,11 +67,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
17
]
}
@@ -82,11 +82,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
19
],
"end": [
- 4,
+ 2,
20
]
}
@@ -97,11 +97,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
22
],
"end": [
- 4,
+ 2,
23
]
}
@@ -112,11 +112,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
24
],
"end": [
- 4,
+ 2,
30
]
}
@@ -127,11 +127,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
32
],
"end": [
- 4,
+ 2,
35
]
}
@@ -142,11 +142,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
36
],
"end": [
- 4,
+ 2,
38
]
}
@@ -157,11 +157,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -172,11 +172,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
10
]
}
@@ -187,11 +187,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
12
],
"end": [
- 5,
+ 3,
15
]
}
@@ -202,11 +202,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
17
],
"end": [
- 5,
+ 3,
22
]
}
@@ -217,11 +217,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
24
],
"end": [
- 5,
+ 3,
26
]
}
@@ -232,11 +232,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
8
]
}
@@ -247,11 +247,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
10
]
}
@@ -262,11 +262,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
12
],
"end": [
- 6,
+ 4,
18
]
}
@@ -277,11 +277,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
19
],
"end": [
- 6,
+ 4,
22
]
}
@@ -292,11 +292,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
24
],
"end": [
- 6,
+ 4,
27
]
}
@@ -307,11 +307,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
28
],
"end": [
- 6,
+ 4,
33
]
}
@@ -322,11 +322,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
35
],
"end": [
- 6,
+ 4,
37
]
}
@@ -340,9 +340,19 @@
"filePaths": [
"function-declarations.go"
],
- "sha1": "e16450a4f5054f826123def384b72eb4946a4544",
+ "patch": [
+ "diff --git a/function-declarations.go b/function-declarations.go",
+ "index e69de29..21da2ea 100644",
+ "--- a/function-declarations.go",
+ "+++ b/function-declarations.go",
+ "@@ -0,0 +1,4 @@",
+ "+func f1() {}",
+ "+func f2(a int, b, c, d string) int {}",
+ "+func f2() (int, error) {}",
+ "+func f2() (result int, err error) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "18f17490d4ca6f4be1bea8d036d146b152e92051"
+ "shas": "26a36f6042d04bfd0685dc779d24c8601a19a4ce..39e0bf0bc911f88d8453f497af5b4e1fba9c1a7b"
}
,{
"testCaseDescription": "go-function-declarations-replacement-insert-test",
@@ -353,11 +363,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -368,11 +378,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -383,11 +393,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
}
@@ -398,11 +408,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
11
],
"end": [
- 4,
+ 2,
14
]
}
@@ -413,11 +423,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
17
]
}
@@ -428,11 +438,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
19
],
"end": [
- 4,
+ 2,
20
]
}
@@ -443,11 +453,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
22
],
"end": [
- 4,
+ 2,
23
]
}
@@ -458,11 +468,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
24
],
"end": [
- 4,
+ 2,
30
]
}
@@ -473,11 +483,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
32
],
"end": [
- 4,
+ 2,
35
]
}
@@ -488,11 +498,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
36
],
"end": [
- 4,
+ 2,
38
]
}
@@ -503,11 +513,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -518,11 +528,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
10
]
}
@@ -533,11 +543,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
12
],
"end": [
- 5,
+ 3,
15
]
}
@@ -548,11 +558,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
17
],
"end": [
- 5,
+ 3,
22
]
}
@@ -563,11 +573,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
24
],
"end": [
- 5,
+ 3,
26
]
}
@@ -578,11 +588,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
8
]
}
@@ -593,11 +603,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
10
]
}
@@ -608,11 +618,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
12
],
"end": [
- 6,
+ 4,
18
]
}
@@ -623,11 +633,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
19
],
"end": [
- 6,
+ 4,
22
]
}
@@ -638,11 +648,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
24
],
"end": [
- 6,
+ 4,
27
]
}
@@ -653,11 +663,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
28
],
"end": [
- 6,
+ 4,
33
]
}
@@ -668,11 +678,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
35
],
"end": [
- 6,
+ 4,
37
]
}
@@ -683,11 +693,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
13
]
}
@@ -698,11 +708,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
}
@@ -713,11 +723,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
9
],
"end": [
- 8,
+ 6,
10
]
}
@@ -728,11 +738,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
11
],
"end": [
- 8,
+ 6,
14
]
}
@@ -743,11 +753,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
16
],
"end": [
- 8,
+ 6,
17
]
}
@@ -758,11 +768,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
19
],
"end": [
- 8,
+ 6,
20
]
}
@@ -773,11 +783,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
22
],
"end": [
- 8,
+ 6,
23
]
}
@@ -788,11 +798,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
24
],
"end": [
- 8,
+ 6,
30
]
}
@@ -803,11 +813,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
32
],
"end": [
- 8,
+ 6,
35
]
}
@@ -818,11 +828,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
36
],
"end": [
- 8,
+ 6,
38
]
}
@@ -833,11 +843,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
8
]
}
@@ -848,11 +858,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
8
],
"end": [
- 9,
+ 7,
10
]
}
@@ -863,11 +873,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
12
],
"end": [
- 9,
+ 7,
15
]
}
@@ -878,11 +888,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
17
],
"end": [
- 9,
+ 7,
22
]
}
@@ -893,11 +903,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
24
],
"end": [
- 9,
+ 7,
26
]
}
@@ -908,11 +918,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
6
],
"end": [
- 10,
+ 8,
8
]
}
@@ -923,11 +933,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
8
],
"end": [
- 10,
+ 8,
10
]
}
@@ -938,11 +948,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
12
],
"end": [
- 10,
+ 8,
18
]
}
@@ -953,11 +963,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
19
],
"end": [
- 10,
+ 8,
22
]
}
@@ -968,11 +978,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
24
],
"end": [
- 10,
+ 8,
27
]
}
@@ -983,11 +993,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
28
],
"end": [
- 10,
+ 8,
33
]
}
@@ -998,11 +1008,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
35
],
"end": [
- 10,
+ 8,
37
]
}
@@ -1016,9 +1026,26 @@
"filePaths": [
"function-declarations.go"
],
- "sha1": "18f17490d4ca6f4be1bea8d036d146b152e92051",
+ "patch": [
+ "diff --git a/function-declarations.go b/function-declarations.go",
+ "index 21da2ea..768679a 100644",
+ "--- a/function-declarations.go",
+ "+++ b/function-declarations.go",
+ "@@ -1,3 +1,11 @@",
+ "+func fa() {}",
+ "+func fb(a int, b, c, d string) int {}",
+ "+func fc() (int, error) {}",
+ "+func fd() (result int, err error) {}",
+ "+func f1() {}",
+ "+func f2(a int, b, c, d string) int {}",
+ "+func f2() (int, error) {}",
+ "+func f2() (result int, err error) {}",
+ " func f1() {}",
+ " func f2(a int, b, c, d string) int {}",
+ " func f2() (int, error) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "23f6af5c91ecb72e357663af0d7c706fac2cbfb8"
+ "shas": "39e0bf0bc911f88d8453f497af5b4e1fba9c1a7b..5e2d36b126b84e7ce03cec16319289469e6a30fb"
}
,{
"testCaseDescription": "go-function-declarations-delete-insert-test",
@@ -1030,48 +1057,48 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
]
},
- "summary": "Replaced the 'fa' identifier with the 'f1' identifier in the f1 function of the 'main' module"
+ "summary": "Replaced the 'fa' identifier with the 'f1' identifier in the f1 function"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -1084,21 +1111,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -1111,21 +1138,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
8
]
},
{
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
8
]
}
@@ -1140,9 +1167,26 @@
"filePaths": [
"function-declarations.go"
],
- "sha1": "23f6af5c91ecb72e357663af0d7c706fac2cbfb8",
+ "patch": [
+ "diff --git a/function-declarations.go b/function-declarations.go",
+ "index 768679a..da899b5 100644",
+ "--- a/function-declarations.go",
+ "+++ b/function-declarations.go",
+ "@@ -1,7 +1,7 @@",
+ "-func fa() {}",
+ "-func fb(a int, b, c, d string) int {}",
+ "-func fc() (int, error) {}",
+ "-func fd() (result int, err error) {}",
+ "+func f1() {}",
+ "+func f2(a int, b, c, d string) int {}",
+ "+func f2() (int, error) {}",
+ "+func f2() (result int, err error) {}",
+ " func f1() {}",
+ " func f2(a int, b, c, d string) int {}",
+ " func f2() (int, error) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "59083835a4a9b8bd20ac68510745db0d0ac98989"
+ "shas": "5e2d36b126b84e7ce03cec16319289469e6a30fb..4745791c3f314164ada7187bd4e6c9fa7990d2bc"
}
,{
"testCaseDescription": "go-function-declarations-replacement-test",
@@ -1154,48 +1198,48 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
]
},
- "summary": "Replaced the 'f1' identifier with the 'fa' identifier in the fa function of the 'main' module"
+ "summary": "Replaced the 'f1' identifier with the 'fa' identifier in the fa function"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -1208,21 +1252,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -1235,21 +1279,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
8
]
},
{
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
8
]
}
@@ -1264,9 +1308,26 @@
"filePaths": [
"function-declarations.go"
],
- "sha1": "59083835a4a9b8bd20ac68510745db0d0ac98989",
+ "patch": [
+ "diff --git a/function-declarations.go b/function-declarations.go",
+ "index da899b5..768679a 100644",
+ "--- a/function-declarations.go",
+ "+++ b/function-declarations.go",
+ "@@ -1,7 +1,7 @@",
+ "-func f1() {}",
+ "-func f2(a int, b, c, d string) int {}",
+ "-func f2() (int, error) {}",
+ "-func f2() (result int, err error) {}",
+ "+func fa() {}",
+ "+func fb(a int, b, c, d string) int {}",
+ "+func fc() (int, error) {}",
+ "+func fd() (result int, err error) {}",
+ " func f1() {}",
+ " func f2(a int, b, c, d string) int {}",
+ " func f2() (int, error) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "062368b7f55602aef4144b77b08ce4b851d580ed"
+ "shas": "4745791c3f314164ada7187bd4e6c9fa7990d2bc..e666c9305cbcd9c4311f9d7f2e1cb0df38fd34a3"
}
,{
"testCaseDescription": "go-function-declarations-delete-replacement-test",
@@ -1277,11 +1338,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -1292,11 +1353,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -1307,11 +1368,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
}
@@ -1322,11 +1383,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
11
],
"end": [
- 4,
+ 2,
14
]
}
@@ -1337,11 +1398,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
17
]
}
@@ -1352,11 +1413,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
19
],
"end": [
- 4,
+ 2,
20
]
}
@@ -1367,11 +1428,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
22
],
"end": [
- 4,
+ 2,
23
]
}
@@ -1382,11 +1443,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
24
],
"end": [
- 4,
+ 2,
30
]
}
@@ -1397,11 +1458,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
32
],
"end": [
- 4,
+ 2,
35
]
}
@@ -1412,11 +1473,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
36
],
"end": [
- 4,
+ 2,
38
]
}
@@ -1427,11 +1488,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -1442,11 +1503,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
10
]
}
@@ -1457,11 +1518,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
12
],
"end": [
- 5,
+ 3,
15
]
}
@@ -1472,11 +1533,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
17
],
"end": [
- 5,
+ 3,
22
]
}
@@ -1487,11 +1548,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
24
],
"end": [
- 5,
+ 3,
26
]
}
@@ -1502,11 +1563,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
8
]
}
@@ -1517,11 +1578,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
10
]
}
@@ -1532,11 +1593,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
12
],
"end": [
- 6,
+ 4,
18
]
}
@@ -1547,11 +1608,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
19
],
"end": [
- 6,
+ 4,
22
]
}
@@ -1562,11 +1623,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
24
],
"end": [
- 6,
+ 4,
27
]
}
@@ -1577,11 +1638,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
28
],
"end": [
- 6,
+ 4,
33
]
}
@@ -1592,11 +1653,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
35
],
"end": [
- 6,
+ 4,
37
]
}
@@ -1607,11 +1668,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
13
]
}
@@ -1622,11 +1683,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
}
@@ -1637,11 +1698,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
9
],
"end": [
- 8,
+ 6,
10
]
}
@@ -1652,11 +1713,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
11
],
"end": [
- 8,
+ 6,
14
]
}
@@ -1667,11 +1728,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
16
],
"end": [
- 8,
+ 6,
17
]
}
@@ -1682,11 +1743,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
19
],
"end": [
- 8,
+ 6,
20
]
}
@@ -1697,11 +1758,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
22
],
"end": [
- 8,
+ 6,
23
]
}
@@ -1712,11 +1773,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
24
],
"end": [
- 8,
+ 6,
30
]
}
@@ -1727,11 +1788,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
32
],
"end": [
- 8,
+ 6,
35
]
}
@@ -1742,11 +1803,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
36
],
"end": [
- 8,
+ 6,
38
]
}
@@ -1757,11 +1818,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
8
]
}
@@ -1772,11 +1833,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
8
],
"end": [
- 9,
+ 7,
10
]
}
@@ -1787,11 +1848,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
12
],
"end": [
- 9,
+ 7,
15
]
}
@@ -1802,11 +1863,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
17
],
"end": [
- 9,
+ 7,
22
]
}
@@ -1817,11 +1878,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
24
],
"end": [
- 9,
+ 7,
26
]
}
@@ -1832,11 +1893,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
6
],
"end": [
- 10,
+ 8,
8
]
}
@@ -1847,11 +1908,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
8
],
"end": [
- 10,
+ 8,
10
]
}
@@ -1862,11 +1923,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
12
],
"end": [
- 10,
+ 8,
18
]
}
@@ -1877,11 +1938,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
19
],
"end": [
- 10,
+ 8,
22
]
}
@@ -1892,11 +1953,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
24
],
"end": [
- 10,
+ 8,
27
]
}
@@ -1907,11 +1968,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
28
],
"end": [
- 10,
+ 8,
33
]
}
@@ -1922,11 +1983,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
35
],
"end": [
- 10,
+ 8,
37
]
}
@@ -1937,11 +1998,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
13
]
}
@@ -1952,11 +2013,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
}
@@ -1967,11 +2028,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
9
],
"end": [
- 8,
+ 6,
10
]
}
@@ -1982,11 +2043,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
11
],
"end": [
- 8,
+ 6,
14
]
}
@@ -1997,11 +2058,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
16
],
"end": [
- 8,
+ 6,
17
]
}
@@ -2012,11 +2073,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
19
],
"end": [
- 8,
+ 6,
20
]
}
@@ -2027,11 +2088,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
22
],
"end": [
- 8,
+ 6,
23
]
}
@@ -2042,11 +2103,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
24
],
"end": [
- 8,
+ 6,
30
]
}
@@ -2057,11 +2118,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
32
],
"end": [
- 8,
+ 6,
35
]
}
@@ -2072,11 +2133,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
36
],
"end": [
- 8,
+ 6,
38
]
}
@@ -2087,11 +2148,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
8
]
}
@@ -2102,11 +2163,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
8
],
"end": [
- 9,
+ 7,
10
]
}
@@ -2117,11 +2178,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
12
],
"end": [
- 9,
+ 7,
15
]
}
@@ -2132,11 +2193,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
17
],
"end": [
- 9,
+ 7,
22
]
}
@@ -2147,11 +2208,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
24
],
"end": [
- 9,
+ 7,
26
]
}
@@ -2162,11 +2223,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
6
],
"end": [
- 10,
+ 8,
8
]
}
@@ -2177,11 +2238,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
8
],
"end": [
- 10,
+ 8,
10
]
}
@@ -2192,11 +2253,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
12
],
"end": [
- 10,
+ 8,
18
]
}
@@ -2207,11 +2268,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
19
],
"end": [
- 10,
+ 8,
22
]
}
@@ -2222,11 +2283,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
24
],
"end": [
- 10,
+ 8,
27
]
}
@@ -2237,11 +2298,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
28
],
"end": [
- 10,
+ 8,
33
]
}
@@ -2252,11 +2313,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
35
],
"end": [
- 10,
+ 8,
37
]
}
@@ -2270,9 +2331,31 @@
"filePaths": [
"function-declarations.go"
],
- "sha1": "062368b7f55602aef4144b77b08ce4b851d580ed",
+ "patch": [
+ "diff --git a/function-declarations.go b/function-declarations.go",
+ "index 768679a..306f918 100644",
+ "--- a/function-declarations.go",
+ "+++ b/function-declarations.go",
+ "@@ -1,12 +1,8 @@",
+ "-func fa() {}",
+ "-func fb(a int, b, c, d string) int {}",
+ "-func fc() (int, error) {}",
+ "-func fd() (result int, err error) {}",
+ "-func f1() {}",
+ "-func f2(a int, b, c, d string) int {}",
+ "-func f2() (int, error) {}",
+ "-func f2() (result int, err error) {}",
+ " func f1() {}",
+ " func f2(a int, b, c, d string) int {}",
+ " func f2() (int, error) {}",
+ " func f2() (result int, err error) {}",
+ "+func fa() {}",
+ "+func fb(a int, b, c, d string) int {}",
+ "+func fc() (int, error) {}",
+ "+func fd() (result int, err error) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "0ccf2eb47d9e2be283f0b091264a22c3e875a917"
+ "shas": "e666c9305cbcd9c4311f9d7f2e1cb0df38fd34a3..72e0169b83a47bf1889b4f2fd259460b1a0d340c"
}
,{
"testCaseDescription": "go-function-declarations-delete-test",
@@ -2283,11 +2366,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -2298,11 +2381,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -2313,11 +2396,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
}
@@ -2328,11 +2411,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
11
],
"end": [
- 4,
+ 2,
14
]
}
@@ -2343,11 +2426,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
17
]
}
@@ -2358,11 +2441,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
19
],
"end": [
- 4,
+ 2,
20
]
}
@@ -2373,11 +2456,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
22
],
"end": [
- 4,
+ 2,
23
]
}
@@ -2388,11 +2471,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
24
],
"end": [
- 4,
+ 2,
30
]
}
@@ -2403,11 +2486,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
32
],
"end": [
- 4,
+ 2,
35
]
}
@@ -2418,11 +2501,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
36
],
"end": [
- 4,
+ 2,
38
]
}
@@ -2433,11 +2516,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -2448,11 +2531,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
10
]
}
@@ -2463,11 +2546,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
12
],
"end": [
- 5,
+ 3,
15
]
}
@@ -2478,11 +2561,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
17
],
"end": [
- 5,
+ 3,
22
]
}
@@ -2493,11 +2576,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
24
],
"end": [
- 5,
+ 3,
26
]
}
@@ -2508,11 +2591,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
8
]
}
@@ -2523,11 +2606,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
10
]
}
@@ -2538,11 +2621,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
12
],
"end": [
- 6,
+ 4,
18
]
}
@@ -2553,11 +2636,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
19
],
"end": [
- 6,
+ 4,
22
]
}
@@ -2568,11 +2651,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
24
],
"end": [
- 6,
+ 4,
27
]
}
@@ -2583,11 +2666,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
28
],
"end": [
- 6,
+ 4,
33
]
}
@@ -2598,11 +2681,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
35
],
"end": [
- 6,
+ 4,
37
]
}
@@ -2616,9 +2699,22 @@
"filePaths": [
"function-declarations.go"
],
- "sha1": "0ccf2eb47d9e2be283f0b091264a22c3e875a917",
+ "patch": [
+ "diff --git a/function-declarations.go b/function-declarations.go",
+ "index 306f918..cc84bb3 100644",
+ "--- a/function-declarations.go",
+ "+++ b/function-declarations.go",
+ "@@ -1,7 +1,3 @@",
+ "-func f1() {}",
+ "-func f2(a int, b, c, d string) int {}",
+ "-func f2() (int, error) {}",
+ "-func f2() (result int, err error) {}",
+ " func fa() {}",
+ " func fb(a int, b, c, d string) int {}",
+ " func fc() (int, error) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "bfb865c56b9e1894611b106d63d1b231549fd8bd"
+ "shas": "72e0169b83a47bf1889b4f2fd259460b1a0d340c..b267320f580c32e85394e065aecd873fc4e72411"
}
,{
"testCaseDescription": "go-function-declarations-delete-rest-test",
@@ -2629,11 +2725,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -2644,11 +2740,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -2659,11 +2755,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
}
@@ -2674,11 +2770,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
11
],
"end": [
- 4,
+ 2,
14
]
}
@@ -2689,11 +2785,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
17
]
}
@@ -2704,11 +2800,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
19
],
"end": [
- 4,
+ 2,
20
]
}
@@ -2719,11 +2815,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
22
],
"end": [
- 4,
+ 2,
23
]
}
@@ -2734,11 +2830,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
24
],
"end": [
- 4,
+ 2,
30
]
}
@@ -2749,11 +2845,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
32
],
"end": [
- 4,
+ 2,
35
]
}
@@ -2764,11 +2860,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
36
],
"end": [
- 4,
+ 2,
38
]
}
@@ -2779,11 +2875,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -2794,11 +2890,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
10
]
}
@@ -2809,11 +2905,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
12
],
"end": [
- 5,
+ 3,
15
]
}
@@ -2824,11 +2920,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
17
],
"end": [
- 5,
+ 3,
22
]
}
@@ -2839,11 +2935,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
24
],
"end": [
- 5,
+ 3,
26
]
}
@@ -2854,11 +2950,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
8
]
}
@@ -2869,11 +2965,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
10
]
}
@@ -2884,11 +2980,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
12
],
"end": [
- 6,
+ 4,
18
]
}
@@ -2899,11 +2995,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
19
],
"end": [
- 6,
+ 4,
22
]
}
@@ -2914,11 +3010,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
24
],
"end": [
- 6,
+ 4,
27
]
}
@@ -2929,11 +3025,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
28
],
"end": [
- 6,
+ 4,
33
]
}
@@ -2944,11 +3040,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
35
],
"end": [
- 6,
+ 4,
37
]
}
@@ -2962,7 +3058,17 @@
"filePaths": [
"function-declarations.go"
],
- "sha1": "bfb865c56b9e1894611b106d63d1b231549fd8bd",
+ "patch": [
+ "diff --git a/function-declarations.go b/function-declarations.go",
+ "index cc84bb3..e69de29 100644",
+ "--- a/function-declarations.go",
+ "+++ b/function-declarations.go",
+ "@@ -1,4 +0,0 @@",
+ "-func fa() {}",
+ "-func fb(a int, b, c, d string) int {}",
+ "-func fc() (int, error) {}",
+ "-func fd() (result int, err error) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3859e3f291b6fe933be02dbc730935422b0aafb0"
+ "shas": "b267320f580c32e85394e065aecd873fc4e72411..9096649c53a965576d44aa8d1b52f7b63d420fea"
}]
diff --git a/test/corpus/diff-summaries/go/function-literals.json b/test/corpus/diff-summaries/go/function-literals.json
index c77747a4e..590bb2af4 100644
--- a/test/corpus/diff-summaries/go/function-literals.json
+++ b/test/corpus/diff-summaries/go/function-literals.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -25,9 +25,18 @@
"filePaths": [
"function-literals.go"
],
- "sha1": "feb6123e4d38848977a42544b3bae6334aecf1e0",
+ "patch": [
+ "diff --git a/function-literals.go b/function-literals.go",
+ "index e69de29..49cbe77 100644",
+ "--- a/function-literals.go",
+ "+++ b/function-literals.go",
+ "@@ -0,0 +1,3 @@",
+ "+const s1 = func(s string) (int, int) {",
+ "+return 1, 2",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "14647fcfa4649e9784df604fefe4128a4af732e7"
+ "shas": "67f60ac0f2697ef8db7d2d1dba1a0b6528d97d51..8755974c3cd7ac6f2006d4e0414296eb9db38d7e"
}
,{
"testCaseDescription": "go-function-literals-replacement-insert-test",
@@ -38,11 +47,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -53,11 +62,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -71,9 +80,24 @@
"filePaths": [
"function-literals.go"
],
- "sha1": "14647fcfa4649e9784df604fefe4128a4af732e7",
+ "patch": [
+ "diff --git a/function-literals.go b/function-literals.go",
+ "index 49cbe77..913c35a 100644",
+ "--- a/function-literals.go",
+ "+++ b/function-literals.go",
+ "@@ -1,3 +1,9 @@",
+ "+const s1 = func(b int) (string, string) {",
+ "+return 1, 2",
+ "+}",
+ "+const s1 = func(s string) (int, int) {",
+ "+return 1, 2",
+ "+}",
+ " const s1 = func(s string) (int, int) {",
+ " return 1, 2",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "089bc8da72a692d35ffacd1ecf61cb5558608ad6"
+ "shas": "8755974c3cd7ac6f2006d4e0414296eb9db38d7e..ee675e2f15860cd9206b37838cbcaff58523fdba"
}
,{
"testCaseDescription": "go-function-literals-delete-insert-test",
@@ -85,54 +109,54 @@
"replace": [
{
"start": [
- 3,
+ 1,
17
],
"end": [
- 3,
+ 1,
18
]
},
{
"start": [
- 3,
+ 1,
17
],
"end": [
- 3,
+ 1,
18
]
}
]
},
- "summary": "Replaced the 'b' identifier with the 's' identifier in the s1 variable of the 'main' module"
+ "summary": "Replaced the 'b' identifier with the 's' identifier in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
19
],
"end": [
- 3,
+ 1,
22
]
},
{
"start": [
- 3,
+ 1,
19
],
"end": [
- 3,
+ 1,
25
]
}
]
},
- "summary": "Replaced the 'int' identifier with the 'string' identifier in the s1 variable of the 'main' module"
+ "summary": "Replaced the 'int' identifier with the 'string' identifier in the s1 variable"
}
]
},
@@ -141,9 +165,20 @@
"filePaths": [
"function-literals.go"
],
- "sha1": "089bc8da72a692d35ffacd1ecf61cb5558608ad6",
+ "patch": [
+ "diff --git a/function-literals.go b/function-literals.go",
+ "index 913c35a..731e2c6 100644",
+ "--- a/function-literals.go",
+ "+++ b/function-literals.go",
+ "@@ -1,4 +1,4 @@",
+ "-const s1 = func(b int) (string, string) {",
+ "+const s1 = func(s string) (int, int) {",
+ " return 1, 2",
+ " }",
+ " const s1 = func(s string) (int, int) {"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "fd04c7101ea4fada80892f6d8266453324fc8bf7"
+ "shas": "ee675e2f15860cd9206b37838cbcaff58523fdba..a251d3cd5feeb8cfe7a47551c659b0b16e5a2d9f"
}
,{
"testCaseDescription": "go-function-literals-replacement-test",
@@ -155,54 +190,54 @@
"replace": [
{
"start": [
- 3,
+ 1,
17
],
"end": [
- 3,
+ 1,
18
]
},
{
"start": [
- 3,
+ 1,
17
],
"end": [
- 3,
+ 1,
18
]
}
]
},
- "summary": "Replaced the 's' identifier with the 'b' identifier in the s1 variable of the 'main' module"
+ "summary": "Replaced the 's' identifier with the 'b' identifier in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
19
],
"end": [
- 3,
+ 1,
25
]
},
{
"start": [
- 3,
+ 1,
19
],
"end": [
- 3,
+ 1,
22
]
}
]
},
- "summary": "Replaced the 'string' identifier with the 'int' identifier in the s1 variable of the 'main' module"
+ "summary": "Replaced the 'string' identifier with the 'int' identifier in the s1 variable"
}
]
},
@@ -211,9 +246,20 @@
"filePaths": [
"function-literals.go"
],
- "sha1": "fd04c7101ea4fada80892f6d8266453324fc8bf7",
+ "patch": [
+ "diff --git a/function-literals.go b/function-literals.go",
+ "index 731e2c6..913c35a 100644",
+ "--- a/function-literals.go",
+ "+++ b/function-literals.go",
+ "@@ -1,4 +1,4 @@",
+ "-const s1 = func(s string) (int, int) {",
+ "+const s1 = func(b int) (string, string) {",
+ " return 1, 2",
+ " }",
+ " const s1 = func(s string) (int, int) {"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3d746e3f13a4392548edef656eeb9f8e7fa46ad7"
+ "shas": "a251d3cd5feeb8cfe7a47551c659b0b16e5a2d9f..ecfe71d5501411a8c39f306bd98ce8972e655c6f"
}
,{
"testCaseDescription": "go-function-literals-delete-replacement-test",
@@ -224,11 +270,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -239,11 +285,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -254,11 +300,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -272,9 +318,25 @@
"filePaths": [
"function-literals.go"
],
- "sha1": "3d746e3f13a4392548edef656eeb9f8e7fa46ad7",
+ "patch": [
+ "diff --git a/function-literals.go b/function-literals.go",
+ "index 913c35a..51820bc 100644",
+ "--- a/function-literals.go",
+ "+++ b/function-literals.go",
+ "@@ -1,9 +1,6 @@",
+ "-const s1 = func(b int) (string, string) {",
+ "-return 1, 2",
+ "-}",
+ " const s1 = func(s string) (int, int) {",
+ " return 1, 2",
+ " }",
+ "-const s1 = func(s string) (int, int) {",
+ "+const s1 = func(b int) (string, string) {",
+ " return 1, 2",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "49f2d11ce6eeb1be2843f138688487c077222380"
+ "shas": "ecfe71d5501411a8c39f306bd98ce8972e655c6f..aaf5cae89acd940e7de671e5ee7bde85182c18a6"
}
,{
"testCaseDescription": "go-function-literals-delete-test",
@@ -285,11 +347,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -303,9 +365,21 @@
"filePaths": [
"function-literals.go"
],
- "sha1": "49f2d11ce6eeb1be2843f138688487c077222380",
+ "patch": [
+ "diff --git a/function-literals.go b/function-literals.go",
+ "index 51820bc..d21dc2d 100644",
+ "--- a/function-literals.go",
+ "+++ b/function-literals.go",
+ "@@ -1,6 +1,3 @@",
+ "-const s1 = func(s string) (int, int) {",
+ "-return 1, 2",
+ "-}",
+ " const s1 = func(b int) (string, string) {",
+ " return 1, 2",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3f3560e2bd7986b84d183880a6709ba0d301722d"
+ "shas": "aaf5cae89acd940e7de671e5ee7bde85182c18a6..1619b15c7c4717361edf049d214759493d0cdc29"
}
,{
"testCaseDescription": "go-function-literals-delete-rest-test",
@@ -316,11 +390,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -334,7 +408,16 @@
"filePaths": [
"function-literals.go"
],
- "sha1": "3f3560e2bd7986b84d183880a6709ba0d301722d",
+ "patch": [
+ "diff --git a/function-literals.go b/function-literals.go",
+ "index d21dc2d..e69de29 100644",
+ "--- a/function-literals.go",
+ "+++ b/function-literals.go",
+ "@@ -1,3 +0,0 @@",
+ "-const s1 = func(b int) (string, string) {",
+ "-return 1, 2",
+ "-}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f99392e84d40bc621fdc924228e731d179062c0b"
+ "shas": "1619b15c7c4717361edf049d214759493d0cdc29..47227a5c2dd60f353b45407e2d7695a53dc5bab9"
}]
diff --git a/test/corpus/diff-summaries/go/function-types.json b/test/corpus/diff-summaries/go/function-types.json
index d6c6a391c..d5ef31e37 100644
--- a/test/corpus/diff-summaries/go/function-types.json
+++ b/test/corpus/diff-summaries/go/function-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
11
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
13
],
"end": [
- 4,
+ 2,
16
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -67,11 +67,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
11
]
}
@@ -82,11 +82,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
13
],
"end": [
- 5,
+ 3,
19
]
}
@@ -97,11 +97,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
22
],
"end": [
- 5,
+ 3,
26
]
}
@@ -112,11 +112,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
28
],
"end": [
- 5,
+ 3,
33
]
}
@@ -130,9 +130,19 @@
"filePaths": [
"function-types.go"
],
- "sha1": "aaf85bbdfa8ebd0c5c6eb74df937ad3e46d6a51e",
+ "patch": [
+ "diff --git a/function-types.go b/function-types.go",
+ "index e69de29..17987a3 100644",
+ "--- a/function-types.go",
+ "+++ b/function-types.go",
+ "@@ -0,0 +1,4 @@",
+ "+type (",
+ "+a func(int) int",
+ "+b func(int, string) (bool, error)",
+ "+)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f3b087e74afcb7e771a6f712ef632a94292c33c5"
+ "shas": "f7bf78dc6e8a6f8dc89e11e588e1661394381c0d..cc5a000625fb6bafbfba4f401635c45ded2b5bf9"
}
,{
"testCaseDescription": "go-function-types-replacement-insert-test",
@@ -143,11 +153,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -158,11 +168,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
14
]
}
@@ -173,11 +183,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
22
]
}
@@ -188,11 +198,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -203,11 +213,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
14
]
}
@@ -218,11 +228,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
16
],
"end": [
- 5,
+ 3,
19
]
}
@@ -233,11 +243,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
26
],
"end": [
- 5,
+ 3,
27
]
}
@@ -248,11 +258,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
28
],
"end": [
- 5,
+ 3,
33
]
}
@@ -263,11 +273,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -278,11 +288,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
8
],
"end": [
- 8,
+ 6,
11
]
}
@@ -293,11 +303,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
13
],
"end": [
- 8,
+ 6,
16
]
}
@@ -308,11 +318,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
2
]
}
@@ -323,11 +333,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
8
],
"end": [
- 9,
+ 7,
11
]
}
@@ -338,11 +348,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
13
],
"end": [
- 9,
+ 7,
19
]
}
@@ -353,11 +363,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
22
],
"end": [
- 9,
+ 7,
26
]
}
@@ -368,11 +378,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
28
],
"end": [
- 9,
+ 7,
33
]
}
@@ -386,9 +396,27 @@
"filePaths": [
"function-types.go"
],
- "sha1": "f3b087e74afcb7e771a6f712ef632a94292c33c5",
+ "patch": [
+ "diff --git a/function-types.go b/function-types.go",
+ "index 17987a3..e3dad40 100644",
+ "--- a/function-types.go",
+ "+++ b/function-types.go",
+ "@@ -1,4 +1,12 @@",
+ " type (",
+ "+x func(string) string",
+ "+y func(string, int) (chan, error)",
+ "+)",
+ "+type (",
+ "+a func(int) int",
+ "+b func(int, string) (bool, error)",
+ "+)",
+ "+type (",
+ " a func(int) int",
+ " b func(int, string) (bool, error)",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "1c48ef08aa7dd37ea68991c3148896b6854cb04c"
+ "shas": "cc5a000625fb6bafbfba4f401635c45ded2b5bf9..c2e26e55f3af2df5c73c0a46cfe638a312c6a2bc"
}
,{
"testCaseDescription": "go-function-types-delete-insert-test",
@@ -397,136 +425,88 @@
"function-types.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 2
- ]
- },
- {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 2
- ]
- }
- ]
- },
- "summary": "Replaced the 'x' identifier with the 'a' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
- 8
- ],
- "end": [
- 4,
- 14
- ]
- },
- {
- "start": [
- 4,
- 8
- ],
- "end": [
- 4,
- 11
- ]
- }
- ]
- },
- "summary": "Replaced the 'string' identifier with the 'int' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
- 16
- ],
- "end": [
- 4,
- 22
- ]
- },
- {
- "start": [
- 4,
- 13
- ],
- "end": [
- 4,
- 16
- ]
- }
- ]
- },
- "summary": "Replaced the 'string' identifier with the 'int' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 5,
- 1
- ],
- "end": [
- 5,
- 2
- ]
- },
- {
- "start": [
- 5,
- 1
- ],
- "end": [
- 5,
- 2
- ]
- }
- ]
- },
- "summary": "Replaced the 'y' identifier with the 'b' identifier"
- },
- {
- "span": {
- "delete": {
+ "insert": {
"start": [
- 5,
- 8
+ 2,
+ 1
],
"end": [
- 5,
- 14
+ 2,
+ 2
]
}
},
- "summary": "Deleted the 'string' identifier"
+ "summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
- 5,
+ 2,
+ 8
+ ],
+ "end": [
+ 2,
+ 11
+ ]
+ }
+ },
+ "summary": "Added the 'int' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
13
],
"end": [
- 5,
+ 2,
+ 16
+ ]
+ }
+ },
+ "summary": "Added the 'int' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 8
+ ],
+ "end": [
+ 3,
+ 11
+ ]
+ }
+ },
+ "summary": "Added the 'int' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 13
+ ],
+ "end": [
+ 3,
19
]
}
@@ -537,11 +517,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
22
],
"end": [
- 5,
+ 3,
26
]
}
@@ -550,227 +530,13 @@
},
{
"span": {
- "delete": {
+ "insert": {
"start": [
- 5,
- 26
- ],
- "end": [
- 5,
- 27
- ]
- }
- },
- "summary": "Deleted the ',' ERROR"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
+ 3,
28
],
"end": [
- 5,
- 33
- ]
- }
- },
- "summary": "Deleted the 'error' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 28
- ],
- "end": [
- 5,
- 33
- ]
- }
- },
- "summary": "Added the 'error' identifier"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "function-types.go"
- ],
- "sha1": "1c48ef08aa7dd37ea68991c3148896b6854cb04c",
- "gitDir": "test/corpus/repos/go",
- "sha2": "b6b98ec5f5396c1e2ec7554919a5e1ccd0fb6359"
-}
-,{
- "testCaseDescription": "go-function-types-replacement-test",
- "expectedResult": {
- "changes": {
- "function-types.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 2
- ]
- },
- {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 2
- ]
- }
- ]
- },
- "summary": "Replaced the 'a' identifier with the 'x' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
- 8
- ],
- "end": [
- 4,
- 11
- ]
- },
- {
- "start": [
- 4,
- 8
- ],
- "end": [
- 4,
- 14
- ]
- }
- ]
- },
- "summary": "Replaced the 'int' identifier with the 'string' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
- 13
- ],
- "end": [
- 4,
- 16
- ]
- },
- {
- "start": [
- 4,
- 16
- ],
- "end": [
- 4,
- 22
- ]
- }
- ]
- },
- "summary": "Replaced the 'int' identifier with the 'string' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 5,
- 1
- ],
- "end": [
- 5,
- 2
- ]
- },
- {
- "start": [
- 5,
- 1
- ],
- "end": [
- 5,
- 2
- ]
- }
- ]
- },
- "summary": "Replaced the 'b' identifier with the 'y' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 8
- ],
- "end": [
- 5,
- 11
- ]
- }
- },
- "summary": "Deleted the 'int' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 16
- ],
- "end": [
- 5,
- 19
- ]
- }
- },
- "summary": "Added the 'int' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 26
- ],
- "end": [
- 5,
- 27
- ]
- }
- },
- "summary": "Added the ',' ERROR"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 28
- ],
- "end": [
- 5,
+ 3,
33
]
}
@@ -781,57 +547,11 @@
"span": {
"delete": {
"start": [
- 5,
- 22
- ],
- "end": [
- 5,
- 26
- ]
- }
- },
- "summary": "Deleted the 'bool' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 28
- ],
- "end": [
- 5,
- 33
- ]
- }
- },
- "summary": "Deleted the 'error' identifier"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "function-types.go"
- ],
- "sha1": "b6b98ec5f5396c1e2ec7554919a5e1ccd0fb6359",
- "gitDir": "test/corpus/repos/go",
- "sha2": "39567166784ff679ea59c24ff0c92f589fb2af3b"
-}
-,{
- "testCaseDescription": "go-function-types-delete-replacement-test",
- "expectedResult": {
- "changes": {
- "function-types.go": [
- {
- "span": {
- "delete": {
- "start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -842,11 +562,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
14
]
}
@@ -857,11 +577,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
16
],
"end": [
- 4,
+ 2,
22
]
}
@@ -872,11 +592,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -887,11 +607,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
14
]
}
@@ -902,11 +622,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
16
],
"end": [
- 5,
+ 3,
19
]
}
@@ -917,11 +637,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
26
],
"end": [
- 5,
+ 3,
27
]
}
@@ -932,146 +652,56 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
28
],
"end": [
- 5,
+ 3,
33
]
}
},
"summary": "Deleted the 'error' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 1
- ],
- "end": [
- 8,
- 2
- ]
- }
- },
- "summary": "Deleted the 'a' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 8
- ],
- "end": [
- 8,
- 11
- ]
- }
- },
- "summary": "Deleted the 'int' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 13
- ],
- "end": [
- 8,
- 16
- ]
- }
- },
- "summary": "Deleted the 'int' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 9,
- 1
- ],
- "end": [
- 9,
- 2
- ]
- }
- },
- "summary": "Deleted the 'b' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 9,
- 8
- ],
- "end": [
- 9,
- 11
- ]
- }
- },
- "summary": "Deleted the 'int' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 9,
- 13
- ],
- "end": [
- 9,
- 19
- ]
- }
- },
- "summary": "Deleted the 'string' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 9,
- 22
- ],
- "end": [
- 9,
- 26
- ]
- }
- },
- "summary": "Deleted the 'bool' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 9,
- 28
- ],
- "end": [
- 9,
- 33
- ]
- }
- },
- "summary": "Deleted the 'error' identifier"
- },
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "function-types.go"
+ ],
+ "patch": [
+ "diff --git a/function-types.go b/function-types.go",
+ "index e3dad40..cf4da5d 100644",
+ "--- a/function-types.go",
+ "+++ b/function-types.go",
+ "@@ -1,6 +1,6 @@",
+ " type (",
+ "-x func(string) string",
+ "-y func(string, int) (chan, error)",
+ "+a func(int) int",
+ "+b func(int, string) (bool, error)",
+ " )",
+ " type (",
+ " a func(int) int"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "c2e26e55f3af2df5c73c0a46cfe638a312c6a2bc..05a86172d0eaa1bced1e55b5b80b729ad3efee30"
+}
+,{
+ "testCaseDescription": "go-function-types-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "function-types.go": [
{
"span": {
"insert": {
"start": [
- 8,
+ 2,
1
],
"end": [
- 8,
+ 2,
2
]
}
@@ -1082,11 +712,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 2,
8
],
"end": [
- 8,
+ 2,
14
]
}
@@ -1097,11 +727,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 2,
16
],
"end": [
- 8,
+ 2,
22
]
}
@@ -1112,11 +742,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 3,
1
],
"end": [
- 9,
+ 3,
2
]
}
@@ -1127,11 +757,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 3,
8
],
"end": [
- 9,
+ 3,
14
]
}
@@ -1142,11 +772,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 3,
16
],
"end": [
- 9,
+ 3,
19
]
}
@@ -1157,11 +787,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 3,
26
],
"end": [
- 9,
+ 3,
27
]
}
@@ -1172,11 +802,521 @@
"span": {
"insert": {
"start": [
- 9,
+ 3,
28
],
"end": [
- 9,
+ 3,
+ 33
+ ]
+ }
+ },
+ "summary": "Added the 'error' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 8
+ ],
+ "end": [
+ 2,
+ 11
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 13
+ ],
+ "end": [
+ 2,
+ 16
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 8
+ ],
+ "end": [
+ 3,
+ 11
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 13
+ ],
+ "end": [
+ 3,
+ 19
+ ]
+ }
+ },
+ "summary": "Deleted the 'string' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 22
+ ],
+ "end": [
+ 3,
+ 26
+ ]
+ }
+ },
+ "summary": "Deleted the 'bool' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 28
+ ],
+ "end": [
+ 3,
+ 33
+ ]
+ }
+ },
+ "summary": "Deleted the 'error' identifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "function-types.go"
+ ],
+ "patch": [
+ "diff --git a/function-types.go b/function-types.go",
+ "index cf4da5d..e3dad40 100644",
+ "--- a/function-types.go",
+ "+++ b/function-types.go",
+ "@@ -1,6 +1,6 @@",
+ " type (",
+ "-a func(int) int",
+ "-b func(int, string) (bool, error)",
+ "+x func(string) string",
+ "+y func(string, int) (chan, error)",
+ " )",
+ " type (",
+ " a func(int) int"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "05a86172d0eaa1bced1e55b5b80b729ad3efee30..3073170a4ab5ecc6b6bea2befa1613a2598db5f1"
+}
+,{
+ "testCaseDescription": "go-function-types-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "function-types.go": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'x' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 8
+ ],
+ "end": [
+ 2,
+ 14
+ ]
+ }
+ },
+ "summary": "Deleted the 'string' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 16
+ ],
+ "end": [
+ 2,
+ 22
+ ]
+ }
+ },
+ "summary": "Deleted the 'string' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'y' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 8
+ ],
+ "end": [
+ 3,
+ 14
+ ]
+ }
+ },
+ "summary": "Deleted the 'string' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 16
+ ],
+ "end": [
+ 3,
+ 19
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 26
+ ],
+ "end": [
+ 3,
+ 27
+ ]
+ }
+ },
+ "summary": "Deleted the ',' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 28
+ ],
+ "end": [
+ 3,
+ 33
+ ]
+ }
+ },
+ "summary": "Deleted the 'error' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 8
+ ],
+ "end": [
+ 6,
+ 11
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 13
+ ],
+ "end": [
+ 6,
+ 16
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 8
+ ],
+ "end": [
+ 7,
+ 11
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 13
+ ],
+ "end": [
+ 7,
+ 19
+ ]
+ }
+ },
+ "summary": "Deleted the 'string' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 22
+ ],
+ "end": [
+ 7,
+ 26
+ ]
+ }
+ },
+ "summary": "Deleted the 'bool' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 28
+ ],
+ "end": [
+ 7,
+ 33
+ ]
+ }
+ },
+ "summary": "Deleted the 'error' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'x' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 8
+ ],
+ "end": [
+ 6,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the 'string' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 16
+ ],
+ "end": [
+ 6,
+ 22
+ ]
+ }
+ },
+ "summary": "Added the 'string' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'y' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 8
+ ],
+ "end": [
+ 7,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the 'string' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 16
+ ],
+ "end": [
+ 7,
+ 19
+ ]
+ }
+ },
+ "summary": "Added the 'int' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 26
+ ],
+ "end": [
+ 7,
+ 27
+ ]
+ }
+ },
+ "summary": "Added the ',' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 28
+ ],
+ "end": [
+ 7,
33
]
}
@@ -1190,9 +1330,29 @@
"filePaths": [
"function-types.go"
],
- "sha1": "39567166784ff679ea59c24ff0c92f589fb2af3b",
+ "patch": [
+ "diff --git a/function-types.go b/function-types.go",
+ "index e3dad40..cc0d209 100644",
+ "--- a/function-types.go",
+ "+++ b/function-types.go",
+ "@@ -1,12 +1,8 @@",
+ " type (",
+ "-x func(string) string",
+ "-y func(string, int) (chan, error)",
+ "-)",
+ "-type (",
+ " a func(int) int",
+ " b func(int, string) (bool, error)",
+ " )",
+ " type (",
+ "-a func(int) int",
+ "-b func(int, string) (bool, error)",
+ "+x func(string) string",
+ "+y func(string, int) (chan, error)",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "30b9f649075f03e35a5d30c11d9b3c300a439cc1"
+ "shas": "3073170a4ab5ecc6b6bea2befa1613a2598db5f1..6f718d79236059d2bf226696aa32cdbd6d1a5d34"
}
,{
"testCaseDescription": "go-function-types-delete-test",
@@ -1201,13 +1361,133 @@
"function-types.go": [
{
"span": {
- "delete": {
+ "insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'x' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 8
+ ],
+ "end": [
+ 2,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the 'string' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 16
+ ],
+ "end": [
+ 2,
+ 22
+ ]
+ }
+ },
+ "summary": "Added the 'string' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'y' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 8
+ ],
+ "end": [
+ 3,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the 'string' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 16
+ ],
+ "end": [
+ 3,
+ 19
+ ]
+ }
+ },
+ "summary": "Added the 'int' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 26
+ ],
+ "end": [
+ 3,
+ 27
+ ]
+ }
+ },
+ "summary": "Added the ',' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 28
+ ],
+ "end": [
+ 3,
+ 33
+ ]
+ }
+ },
+ "summary": "Added the 'error' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
2
]
}
@@ -1218,11 +1498,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
11
]
}
@@ -1233,11 +1513,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
13
],
"end": [
- 4,
+ 2,
16
]
}
@@ -1248,11 +1528,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -1263,11 +1543,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
11
]
}
@@ -1278,11 +1558,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
13
],
"end": [
- 5,
+ 3,
19
]
}
@@ -1293,11 +1573,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
22
],
"end": [
- 5,
+ 3,
26
]
}
@@ -1308,42 +1588,26 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
28
],
"end": [
- 5,
+ 3,
33
]
}
},
"summary": "Deleted the 'error' identifier"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "function-types.go"
- ],
- "sha1": "30b9f649075f03e35a5d30c11d9b3c300a439cc1",
- "gitDir": "test/corpus/repos/go",
- "sha2": "5ed9a7cd06807d6afd5c95f2001442093f3f6ebd"
-}
-,{
- "testCaseDescription": "go-function-types-delete-rest-test",
- "expectedResult": {
- "changes": {
- "function-types.go": [
+ },
{
"span": {
"delete": {
"start": [
- 4,
+ 6,
1
],
"end": [
- 4,
+ 6,
2
]
}
@@ -1354,11 +1618,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 6,
8
],
"end": [
- 4,
+ 6,
14
]
}
@@ -1369,11 +1633,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 6,
16
],
"end": [
- 4,
+ 6,
22
]
}
@@ -1384,11 +1648,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 7,
1
],
"end": [
- 5,
+ 7,
2
]
}
@@ -1399,11 +1663,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 7,
8
],
"end": [
- 5,
+ 7,
14
]
}
@@ -1414,11 +1678,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 7,
16
],
"end": [
- 5,
+ 7,
19
]
}
@@ -1429,11 +1693,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 7,
26
],
"end": [
- 5,
+ 7,
27
]
}
@@ -1444,11 +1708,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 7,
28
],
"end": [
- 5,
+ 7,
33
]
}
@@ -1462,7 +1726,167 @@
"filePaths": [
"function-types.go"
],
- "sha1": "5ed9a7cd06807d6afd5c95f2001442093f3f6ebd",
+ "patch": [
+ "diff --git a/function-types.go b/function-types.go",
+ "index cc0d209..5deebe6 100644",
+ "--- a/function-types.go",
+ "+++ b/function-types.go",
+ "@@ -1,8 +1,4 @@",
+ " type (",
+ "-a func(int) int",
+ "-b func(int, string) (bool, error)",
+ "-)",
+ "-type (",
+ " x func(string) string",
+ " y func(string, int) (chan, error)",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "67c9b2b4c39ded2b611f972919a115ed4b8759da"
+ "shas": "6f718d79236059d2bf226696aa32cdbd6d1a5d34..911f3760eb4f1e63a0ca9cdef8ee067d210f356d"
+}
+,{
+ "testCaseDescription": "go-function-types-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "function-types.go": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'x' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 8
+ ],
+ "end": [
+ 2,
+ 14
+ ]
+ }
+ },
+ "summary": "Deleted the 'string' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 16
+ ],
+ "end": [
+ 2,
+ 22
+ ]
+ }
+ },
+ "summary": "Deleted the 'string' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'y' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 8
+ ],
+ "end": [
+ 3,
+ 14
+ ]
+ }
+ },
+ "summary": "Deleted the 'string' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 16
+ ],
+ "end": [
+ 3,
+ 19
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 26
+ ],
+ "end": [
+ 3,
+ 27
+ ]
+ }
+ },
+ "summary": "Deleted the ',' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 28
+ ],
+ "end": [
+ 3,
+ 33
+ ]
+ }
+ },
+ "summary": "Deleted the 'error' identifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "function-types.go"
+ ],
+ "patch": [
+ "diff --git a/function-types.go b/function-types.go",
+ "index 5deebe6..e69de29 100644",
+ "--- a/function-types.go",
+ "+++ b/function-types.go",
+ "@@ -1,4 +0,0 @@",
+ "-type (",
+ "-x func(string) string",
+ "-y func(string, int) (chan, error)",
+ "-)"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "911f3760eb4f1e63a0ca9cdef8ee067d210f356d..72b83c0cd3955c0af628b6cfd369ee028685eeec"
}]
diff --git a/test/corpus/diff-summaries/go/go-and-defer-statements.json b/test/corpus/diff-summaries/go/go-and-defer-statements.json
index fb1340624..c441d53e0 100644
--- a/test/corpus/diff-summaries/go/go-and-defer-statements.json
+++ b/test/corpus/diff-summaries/go/go-and-defer-statements.json
@@ -5,30 +5,33 @@
"go-and-defer-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'identifier()' function call"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 4
+ ],
+ "end": [
+ 2,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the 'identifier()' function call"
}
]
},
@@ -37,9 +40,17 @@
"filePaths": [
"go-and-defer-statements.go"
],
- "sha1": "52c2367740c0d2f7f66fbb1638b6bbe52b8bb586",
+ "patch": [
+ "diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
+ "index e69de29..2638f27 100644",
+ "--- a/go-and-defer-statements.go",
+ "+++ b/go-and-defer-statements.go",
+ "@@ -0,0 +1,2 @@",
+ "+defer x.y()",
+ "+go x.y()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ff145520e936a2f8287e7b7f560e648c86e37d73"
+ "shas": "c169e9683d54586a7fa6eab867dc6eb4eae7e85c..80641345f16131608a18991fe0a29736f5f5b66d"
}
,{
"testCaseDescription": "go-go-and-defer-statements-replacement-insert-test",
@@ -50,11 +61,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
12
]
}
@@ -65,11 +76,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
4
],
"end": [
- 4,
+ 2,
9
]
}
@@ -80,11 +91,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
7
],
"end": [
- 5,
+ 3,
12
]
}
@@ -95,11 +106,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
9
]
}
@@ -113,9 +124,21 @@
"filePaths": [
"go-and-defer-statements.go"
],
- "sha1": "ff145520e936a2f8287e7b7f560e648c86e37d73",
+ "patch": [
+ "diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
+ "index 2638f27..0cb11d5 100644",
+ "--- a/go-and-defer-statements.go",
+ "+++ b/go-and-defer-statements.go",
+ "@@ -1,2 +1,6 @@",
+ "+defer a.b()",
+ "+go c.d()",
+ "+defer x.y()",
+ "+go x.y()",
+ " defer x.y()",
+ " go x.y()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "35d23458ecbda705d91d36133acb3ee06114160e"
+ "shas": "80641345f16131608a18991fe0a29736f5f5b66d..c4bf57adbccc55e8edec2a3e41f7a5e385b41e44"
}
,{
"testCaseDescription": "go-go-and-defer-statements-delete-insert-test",
@@ -127,21 +150,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
8
]
}
@@ -154,21 +177,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
},
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -181,21 +204,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
4
],
"end": [
- 4,
+ 2,
5
]
},
{
"start": [
- 4,
+ 2,
4
],
"end": [
- 4,
+ 2,
5
]
}
@@ -208,21 +231,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -237,9 +260,22 @@
"filePaths": [
"go-and-defer-statements.go"
],
- "sha1": "35d23458ecbda705d91d36133acb3ee06114160e",
+ "patch": [
+ "diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
+ "index 0cb11d5..bdc42aa 100644",
+ "--- a/go-and-defer-statements.go",
+ "+++ b/go-and-defer-statements.go",
+ "@@ -1,5 +1,5 @@",
+ "-defer a.b()",
+ "-go c.d()",
+ "+defer x.y()",
+ "+go x.y()",
+ " defer x.y()",
+ " go x.y()",
+ " defer x.y()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f88c96f73dcf4e7e57a35b85a54babeb4b8be7c1"
+ "shas": "c4bf57adbccc55e8edec2a3e41f7a5e385b41e44..ee1387252f87d4b177e4220468eb3464aca29649"
}
,{
"testCaseDescription": "go-go-and-defer-statements-replacement-test",
@@ -251,21 +287,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
8
]
}
@@ -278,21 +314,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
},
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -305,21 +341,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
4
],
"end": [
- 4,
+ 2,
5
]
},
{
"start": [
- 4,
+ 2,
4
],
"end": [
- 4,
+ 2,
5
]
}
@@ -332,21 +368,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -361,9 +397,22 @@
"filePaths": [
"go-and-defer-statements.go"
],
- "sha1": "f88c96f73dcf4e7e57a35b85a54babeb4b8be7c1",
+ "patch": [
+ "diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
+ "index bdc42aa..0cb11d5 100644",
+ "--- a/go-and-defer-statements.go",
+ "+++ b/go-and-defer-statements.go",
+ "@@ -1,5 +1,5 @@",
+ "-defer x.y()",
+ "-go x.y()",
+ "+defer a.b()",
+ "+go c.d()",
+ " defer x.y()",
+ " go x.y()",
+ " defer x.y()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b0fad2ef7fadce069db33e4d5d351cf07381ad0c"
+ "shas": "ee1387252f87d4b177e4220468eb3464aca29649..cf2d1e4c851ac68b7f34e8e038d2a4f1baed2c29"
}
,{
"testCaseDescription": "go-go-and-defer-statements-delete-replacement-test",
@@ -374,11 +423,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
12
]
}
@@ -389,11 +438,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
4
],
"end": [
- 4,
+ 2,
9
]
}
@@ -404,11 +453,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
7
],
"end": [
- 5,
+ 3,
12
]
}
@@ -419,11 +468,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
9
]
}
@@ -434,11 +483,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
7
],
"end": [
- 5,
+ 3,
12
]
}
@@ -449,11 +498,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
9
]
}
@@ -467,9 +516,23 @@
"filePaths": [
"go-and-defer-statements.go"
],
- "sha1": "b0fad2ef7fadce069db33e4d5d351cf07381ad0c",
+ "patch": [
+ "diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
+ "index 0cb11d5..f18666e 100644",
+ "--- a/go-and-defer-statements.go",
+ "+++ b/go-and-defer-statements.go",
+ "@@ -1,6 +1,4 @@",
+ "-defer a.b()",
+ "-go c.d()",
+ "-defer x.y()",
+ "-go x.y()",
+ " defer x.y()",
+ " go x.y()",
+ "+defer a.b()",
+ "+go c.d()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "23967cd45fb4ea3b1ba4510a47506b8782b1842a"
+ "shas": "cf2d1e4c851ac68b7f34e8e038d2a4f1baed2c29..ac0dbf98bade4304c09fbf1c54659937d25ef4f6"
}
,{
"testCaseDescription": "go-go-and-defer-statements-delete-test",
@@ -480,11 +543,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
12
]
}
@@ -495,11 +558,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
4
],
"end": [
- 4,
+ 2,
9
]
}
@@ -513,9 +576,19 @@
"filePaths": [
"go-and-defer-statements.go"
],
- "sha1": "23967cd45fb4ea3b1ba4510a47506b8782b1842a",
+ "patch": [
+ "diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
+ "index f18666e..eefd2e4 100644",
+ "--- a/go-and-defer-statements.go",
+ "+++ b/go-and-defer-statements.go",
+ "@@ -1,4 +1,2 @@",
+ "-defer x.y()",
+ "-go x.y()",
+ " defer a.b()",
+ " go c.d()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f0dc69f90f6294734196eb47b4391629a1b7ef82"
+ "shas": "ac0dbf98bade4304c09fbf1c54659937d25ef4f6..9d87babf6dd8ad58fecae95e0fe516803ef693af"
}
,{
"testCaseDescription": "go-go-and-defer-statements-delete-rest-test",
@@ -524,30 +597,33 @@
"go-and-defer-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'identifier()' function call"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 4
+ ],
+ "end": [
+ 2,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'identifier()' function call"
}
]
},
@@ -556,7 +632,15 @@
"filePaths": [
"go-and-defer-statements.go"
],
- "sha1": "f0dc69f90f6294734196eb47b4391629a1b7ef82",
+ "patch": [
+ "diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
+ "index eefd2e4..e69de29 100644",
+ "--- a/go-and-defer-statements.go",
+ "+++ b/go-and-defer-statements.go",
+ "@@ -1,2 +0,0 @@",
+ "-defer a.b()",
+ "-go c.d()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c69fcfce40f178714107964705a6370513f7733e"
+ "shas": "9d87babf6dd8ad58fecae95e0fe516803ef693af..b36463027cca058b97d4495c8c08a1ab9ab5cc0a"
}]
diff --git a/test/corpus/diff-summaries/go/grouped-import-declarations.json b/test/corpus/diff-summaries/go/grouped-import-declarations.json
index b397a093d..8388632e6 100644
--- a/test/corpus/diff-summaries/go/grouped-import-declarations.json
+++ b/test/corpus/diff-summaries/go/grouped-import-declarations.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -41,16 +41,16 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
},
- "summary": "Added the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 3, column 1 - line 7, column 2"
+ "summary": "Added the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 1, column 1 - line 5, column 2"
}
]
}
@@ -58,9 +58,20 @@
"filePaths": [
"grouped-import-declarations.go"
],
- "sha1": "60d0595870f22587e7f31bed659faaa89e73c81d",
+ "patch": [
+ "diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
+ "index e69de29..6560136 100644",
+ "--- a/grouped-import-declarations.go",
+ "+++ b/grouped-import-declarations.go",
+ "@@ -0,0 +1,5 @@",
+ "+import (",
+ "+\"net/http\"",
+ "+ . \"some/dsl\"",
+ "+ alias \"some/package\"",
+ "+)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "1fe7a29c5ec7cbbfbbe9c08f0df45e550a37e309"
+ "shas": "49405e780f45c25871a6c2c6a9c4bf847007c59f..cc06896916290333b40603e033a3026be682acd2"
}
,{
"testCaseDescription": "go-grouped-import-declarations-replacement-insert-test",
@@ -71,11 +82,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -86,11 +97,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -101,11 +112,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
2
]
}
@@ -116,11 +127,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
2
]
}
@@ -135,31 +146,31 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
},
- "summary": "Added the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 3, column 1 - line 7, column 2"
+ "summary": "Added the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 1, column 1 - line 5, column 2"
},
{
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
2
]
}
},
- "summary": "Added the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 8, column 1 - line 12, column 2"
+ "summary": "Added the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 6, column 1 - line 10, column 2"
}
]
}
@@ -167,9 +178,29 @@
"filePaths": [
"grouped-import-declarations.go"
],
- "sha1": "1fe7a29c5ec7cbbfbbe9c08f0df45e550a37e309",
+ "patch": [
+ "diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
+ "index 6560136..31d6bd7 100644",
+ "--- a/grouped-import-declarations.go",
+ "+++ b/grouped-import-declarations.go",
+ "@@ -1,4 +1,14 @@",
+ " import (",
+ "+\"net/socket\"",
+ "+ . \"types/dsl\"",
+ "+ alias \"awesome/package\"",
+ "+)",
+ "+import (",
+ "+\"net/http\"",
+ "+ . \"some/dsl\"",
+ "+ alias \"some/package\"",
+ "+)",
+ "+import (",
+ " \"net/http\"",
+ " . \"some/dsl\"",
+ " alias \"some/package\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "bfae8c56020292f9b5b6a6bf4b3a93baca698132"
+ "shas": "cc06896916290333b40603e033a3026be682acd2..ae3d9e278cd263970d3db8098ffa0c1f92467a94"
}
,{
"testCaseDescription": "go-grouped-import-declarations-delete-insert-test",
@@ -181,75 +212,75 @@
"replace": [
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
13
]
},
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
11
]
}
]
},
- "summary": "Replaced the \"net/socket\" string with the \"net/http\" string in the \"net/http\" import statement of the 'main' module"
+ "summary": "Replaced the \"net/socket\" string with the \"net/http\" string in the \"net/http\" import statement"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
16
]
},
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
15
]
}
]
},
- "summary": "Replaced the \"types/dsl\" string with the \"some/dsl\" string in the \"some/dsl\" import statement of the 'main' module"
+ "summary": "Replaced the \"types/dsl\" string with the \"some/dsl\" string in the \"some/dsl\" import statement"
},
{
"span": {
"replace": [
{
"start": [
- 6,
+ 4,
9
],
"end": [
- 6,
+ 4,
26
]
},
{
"start": [
- 6,
+ 4,
9
],
"end": [
- 6,
+ 4,
23
]
}
@@ -264,9 +295,25 @@
"filePaths": [
"grouped-import-declarations.go"
],
- "sha1": "bfae8c56020292f9b5b6a6bf4b3a93baca698132",
+ "patch": [
+ "diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
+ "index 31d6bd7..b045ab3 100644",
+ "--- a/grouped-import-declarations.go",
+ "+++ b/grouped-import-declarations.go",
+ "@@ -1,7 +1,7 @@",
+ " import (",
+ "-\"net/socket\"",
+ "- . \"types/dsl\"",
+ "- alias \"awesome/package\"",
+ "+\"net/http\"",
+ "+ . \"some/dsl\"",
+ "+ alias \"some/package\"",
+ " )",
+ " import (",
+ " \"net/http\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "4486c18ce99e8c00f902916fefae9c8e93e53604"
+ "shas": "ae3d9e278cd263970d3db8098ffa0c1f92467a94..e58383201c252323abe4b3bab9aa34697e646d47"
}
,{
"testCaseDescription": "go-grouped-import-declarations-replacement-test",
@@ -278,75 +325,75 @@
"replace": [
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
11
]
},
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
13
]
}
]
},
- "summary": "Replaced the \"net/http\" string with the \"net/socket\" string in the \"net/socket\" import statement of the 'main' module"
+ "summary": "Replaced the \"net/http\" string with the \"net/socket\" string in the \"net/socket\" import statement"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
15
]
},
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
16
]
}
]
},
- "summary": "Replaced the \"some/dsl\" string with the \"types/dsl\" string in the \"types/dsl\" import statement of the 'main' module"
+ "summary": "Replaced the \"some/dsl\" string with the \"types/dsl\" string in the \"types/dsl\" import statement"
},
{
"span": {
"replace": [
{
"start": [
- 6,
+ 4,
9
],
"end": [
- 6,
+ 4,
23
]
},
{
"start": [
- 6,
+ 4,
9
],
"end": [
- 6,
+ 4,
26
]
}
@@ -361,9 +408,25 @@
"filePaths": [
"grouped-import-declarations.go"
],
- "sha1": "4486c18ce99e8c00f902916fefae9c8e93e53604",
+ "patch": [
+ "diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
+ "index b045ab3..31d6bd7 100644",
+ "--- a/grouped-import-declarations.go",
+ "+++ b/grouped-import-declarations.go",
+ "@@ -1,7 +1,7 @@",
+ " import (",
+ "-\"net/http\"",
+ "- . \"some/dsl\"",
+ "- alias \"some/package\"",
+ "+\"net/socket\"",
+ "+ . \"types/dsl\"",
+ "+ alias \"awesome/package\"",
+ " )",
+ " import (",
+ " \"net/http\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ebeab6442fbe6ebfa96ec494a608838fdeb939d2"
+ "shas": "e58383201c252323abe4b3bab9aa34697e646d47..349362f05c75b2ed25ff9be203d01d1d1653e1d4"
}
,{
"testCaseDescription": "go-grouped-import-declarations-delete-replacement-test",
@@ -374,11 +437,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -389,11 +452,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -404,11 +467,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
2
]
}
@@ -419,11 +482,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
2
]
}
@@ -434,11 +497,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
2
]
}
@@ -449,11 +512,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
2
]
}
@@ -468,46 +531,46 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
},
- "summary": "Deleted the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 3, column 1 - line 7, column 2"
+ "summary": "Deleted the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 1, column 1 - line 5, column 2"
},
{
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
2
]
}
},
- "summary": "Deleted the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 8, column 1 - line 12, column 2"
+ "summary": "Deleted the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 6, column 1 - line 10, column 2"
},
{
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 12,
+ 10,
2
]
}
},
- "summary": "Added the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 8, column 1 - line 12, column 2"
+ "summary": "Added the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 6, column 1 - line 10, column 2"
}
]
}
@@ -515,9 +578,33 @@
"filePaths": [
"grouped-import-declarations.go"
],
- "sha1": "ebeab6442fbe6ebfa96ec494a608838fdeb939d2",
+ "patch": [
+ "diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
+ "index 31d6bd7..62facc6 100644",
+ "--- a/grouped-import-declarations.go",
+ "+++ b/grouped-import-declarations.go",
+ "@@ -1,15 +1,10 @@",
+ " import (",
+ "-\"net/socket\"",
+ "- . \"types/dsl\"",
+ "- alias \"awesome/package\"",
+ "-)",
+ "-import (",
+ " \"net/http\"",
+ " . \"some/dsl\"",
+ " alias \"some/package\"",
+ " )",
+ " import (",
+ "-\"net/http\"",
+ "- . \"some/dsl\"",
+ "- alias \"some/package\"",
+ "+\"net/socket\"",
+ "+ . \"types/dsl\"",
+ "+ alias \"awesome/package\"",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a146a9af4f24e654718d36f735709738ac4aa6fc"
+ "shas": "349362f05c75b2ed25ff9be203d01d1d1653e1d4..96f9229250891a51f9f57e74e7e4b203e2645c56"
}
,{
"testCaseDescription": "go-grouped-import-declarations-delete-test",
@@ -528,11 +615,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -543,11 +630,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -562,16 +649,16 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
},
- "summary": "Deleted the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 3, column 1 - line 7, column 2"
+ "summary": "Deleted the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 1, column 1 - line 5, column 2"
}
]
}
@@ -579,9 +666,24 @@
"filePaths": [
"grouped-import-declarations.go"
],
- "sha1": "a146a9af4f24e654718d36f735709738ac4aa6fc",
+ "patch": [
+ "diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
+ "index 62facc6..e2f9293 100644",
+ "--- a/grouped-import-declarations.go",
+ "+++ b/grouped-import-declarations.go",
+ "@@ -1,9 +1,4 @@",
+ " import (",
+ "-\"net/http\"",
+ "- . \"some/dsl\"",
+ "- alias \"some/package\"",
+ "-)",
+ "-import (",
+ " \"net/socket\"",
+ " . \"types/dsl\"",
+ " alias \"awesome/package\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f81df7eb8f27b1b375c0539beda1cb82f16df0ae"
+ "shas": "96f9229250891a51f9f57e74e7e4b203e2645c56..67cbd59683a26fc0a936ac70b19ebb9074aa5b03"
}
,{
"testCaseDescription": "go-grouped-import-declarations-delete-rest-test",
@@ -592,11 +694,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -607,11 +709,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
@@ -626,16 +728,16 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 7,
+ 5,
2
]
}
},
- "summary": "Deleted the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 3, column 1 - line 7, column 2"
+ "summary": "Deleted the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 1, column 1 - line 5, column 2"
}
]
}
@@ -643,7 +745,18 @@
"filePaths": [
"grouped-import-declarations.go"
],
- "sha1": "f81df7eb8f27b1b375c0539beda1cb82f16df0ae",
+ "patch": [
+ "diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
+ "index e2f9293..e69de29 100644",
+ "--- a/grouped-import-declarations.go",
+ "+++ b/grouped-import-declarations.go",
+ "@@ -1,5 +0,0 @@",
+ "-import (",
+ "-\"net/socket\"",
+ "- . \"types/dsl\"",
+ "- alias \"awesome/package\"",
+ "-)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7d873f0d5579c52294d6b425bd5d9729ac1782e1"
+ "shas": "67cbd59683a26fc0a936ac70b19ebb9074aa5b03..c6aae7f905be036e251d244801d3fd73b49f6c46"
}]
diff --git a/test/corpus/diff-summaries/go/grouped-var-declarations.json b/test/corpus/diff-summaries/go/grouped-var-declarations.json
index 3bae206c8..651e8ce29 100644
--- a/test/corpus/diff-summaries/go/grouped-var-declarations.json
+++ b/test/corpus/diff-summaries/go/grouped-var-declarations.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -40,9 +40,19 @@
"filePaths": [
"grouped-var-declarations.go"
],
- "sha1": "3f6fa7c6f499951a277e9ae6edce3681134ef5d9",
+ "patch": [
+ "diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
+ "index e69de29..c1c0b16 100644",
+ "--- a/grouped-var-declarations.go",
+ "+++ b/grouped-var-declarations.go",
+ "@@ -0,0 +1,4 @@",
+ "+var (",
+ "+zero = 0",
+ "+one = 1",
+ "+)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "6f2161f8593d0ec0dacd2958538ce5fa2a84f6ba"
+ "shas": "7ec7378727f160ff6fb78761d149f5f110898c3e..514932d92bd7fa7d087adb1d4968ff2d1b35d832"
}
,{
"testCaseDescription": "go-grouped-var-declarations-replacement-insert-test",
@@ -53,11 +63,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -68,11 +78,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -83,11 +93,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -98,11 +108,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -116,9 +126,27 @@
"filePaths": [
"grouped-var-declarations.go"
],
- "sha1": "6f2161f8593d0ec0dacd2958538ce5fa2a84f6ba",
+ "patch": [
+ "diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
+ "index c1c0b16..6b9c91d 100644",
+ "--- a/grouped-var-declarations.go",
+ "+++ b/grouped-var-declarations.go",
+ "@@ -1,4 +1,12 @@",
+ " var (",
+ "+a = 0",
+ "+b = 1",
+ "+)",
+ "+var (",
+ "+zero = 0",
+ "+one = 1",
+ "+)",
+ "+var (",
+ " zero = 0",
+ " one = 1",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "aacd0b2f15a856a49e3d7fe131aed23a9c77224f"
+ "shas": "514932d92bd7fa7d087adb1d4968ff2d1b35d832..d8482bba7e246518bcaf8b8759b4ccaf7fd3f41d"
}
,{
"testCaseDescription": "go-grouped-var-declarations-delete-insert-test",
@@ -130,54 +158,54 @@
"replace": [
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
},
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
5
]
}
]
},
- "summary": "Replaced the 'a' identifier with the 'zero' identifier in the zero variable of the 'main' module"
+ "summary": "Replaced the 'a' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
},
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
4
]
}
]
},
- "summary": "Replaced the 'b' identifier with the 'one' identifier in the one variable of the 'main' module"
+ "summary": "Replaced the 'b' identifier with the 'one' identifier in the one variable"
}
]
},
@@ -186,9 +214,23 @@
"filePaths": [
"grouped-var-declarations.go"
],
- "sha1": "aacd0b2f15a856a49e3d7fe131aed23a9c77224f",
+ "patch": [
+ "diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
+ "index 6b9c91d..5ed0e06 100644",
+ "--- a/grouped-var-declarations.go",
+ "+++ b/grouped-var-declarations.go",
+ "@@ -1,6 +1,6 @@",
+ " var (",
+ "-a = 0",
+ "-b = 1",
+ "+zero = 0",
+ "+one = 1",
+ " )",
+ " var (",
+ " zero = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "8d277d6c567a51e3154eb9ee8d7f02f8ecda938e"
+ "shas": "d8482bba7e246518bcaf8b8759b4ccaf7fd3f41d..3221bb9fd5791c127b591e17941faf48d46e11f7"
}
,{
"testCaseDescription": "go-grouped-var-declarations-replacement-test",
@@ -200,54 +242,54 @@
"replace": [
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
5
]
},
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
]
},
- "summary": "Replaced the 'zero' identifier with the 'a' identifier in the a variable of the 'main' module"
+ "summary": "Replaced the 'zero' identifier with the 'a' identifier in the a variable"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
4
]
},
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
]
},
- "summary": "Replaced the 'one' identifier with the 'b' identifier in the b variable of the 'main' module"
+ "summary": "Replaced the 'one' identifier with the 'b' identifier in the b variable"
}
]
},
@@ -256,9 +298,23 @@
"filePaths": [
"grouped-var-declarations.go"
],
- "sha1": "8d277d6c567a51e3154eb9ee8d7f02f8ecda938e",
+ "patch": [
+ "diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
+ "index 5ed0e06..6b9c91d 100644",
+ "--- a/grouped-var-declarations.go",
+ "+++ b/grouped-var-declarations.go",
+ "@@ -1,6 +1,6 @@",
+ " var (",
+ "-zero = 0",
+ "-one = 1",
+ "+a = 0",
+ "+b = 1",
+ " )",
+ " var (",
+ " zero = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "10bfc15216d52a971377c98ada621b65d1f1d762"
+ "shas": "3221bb9fd5791c127b591e17941faf48d46e11f7..eb6cf49333e266ba6255891b55edc54e015cc8dd"
}
,{
"testCaseDescription": "go-grouped-var-declarations-delete-replacement-test",
@@ -269,11 +325,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -284,11 +340,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -299,11 +355,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -314,11 +370,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -329,11 +385,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -344,11 +400,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -362,9 +418,29 @@
"filePaths": [
"grouped-var-declarations.go"
],
- "sha1": "10bfc15216d52a971377c98ada621b65d1f1d762",
+ "patch": [
+ "diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
+ "index 6b9c91d..9094e82 100644",
+ "--- a/grouped-var-declarations.go",
+ "+++ b/grouped-var-declarations.go",
+ "@@ -1,12 +1,8 @@",
+ " var (",
+ "-a = 0",
+ "-b = 1",
+ "-)",
+ "-var (",
+ " zero = 0",
+ " one = 1",
+ " )",
+ " var (",
+ "-zero = 0",
+ "-one = 1",
+ "+a = 0",
+ "+b = 1",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ff81eb523089ada7047b28b1802b8f4ee6ce77d3"
+ "shas": "eb6cf49333e266ba6255891b55edc54e015cc8dd..3973fafa7c0a3f1f3cd2e92462d863df41f3a920"
}
,{
"testCaseDescription": "go-grouped-var-declarations-delete-test",
@@ -375,11 +451,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -390,11 +466,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -408,9 +484,23 @@
"filePaths": [
"grouped-var-declarations.go"
],
- "sha1": "ff81eb523089ada7047b28b1802b8f4ee6ce77d3",
+ "patch": [
+ "diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
+ "index 9094e82..d954576 100644",
+ "--- a/grouped-var-declarations.go",
+ "+++ b/grouped-var-declarations.go",
+ "@@ -1,8 +1,4 @@",
+ " var (",
+ "-zero = 0",
+ "-one = 1",
+ "-)",
+ "-var (",
+ " a = 0",
+ " b = 1",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "706e2dd9a32626624b48a24e0b82d45574ccdbd1"
+ "shas": "3973fafa7c0a3f1f3cd2e92462d863df41f3a920..39e74e79c2f9366472ae046e56a3e0a60d1797e1"
}
,{
"testCaseDescription": "go-grouped-var-declarations-delete-rest-test",
@@ -421,11 +511,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -436,11 +526,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -454,7 +544,17 @@
"filePaths": [
"grouped-var-declarations.go"
],
- "sha1": "706e2dd9a32626624b48a24e0b82d45574ccdbd1",
+ "patch": [
+ "diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
+ "index d954576..e69de29 100644",
+ "--- a/grouped-var-declarations.go",
+ "+++ b/grouped-var-declarations.go",
+ "@@ -1,4 +0,0 @@",
+ "-var (",
+ "-a = 0",
+ "-b = 1",
+ "-)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ad009ae663a027f35bb25867c4aa1375820fd816"
+ "shas": "39e74e79c2f9366472ae046e56a3e0a60d1797e1..c8c183bd98d018d2097fe1ee036d32d979f4919b"
}]
diff --git a/test/corpus/diff-summaries/go/if-statements.json b/test/corpus/diff-summaries/go/if-statements.json
index 7fca43baa..4dbba6ca8 100644
--- a/test/corpus/diff-summaries/go/if-statements.json
+++ b/test/corpus/diff-summaries/go/if-statements.json
@@ -1,48 +1,5 @@
[{
"testCaseDescription": "go-if-statements-insert-test",
- "expectedResult": {
- "changes": {
- "if-statements.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
- },
- "summary": "Replaced the 'main' module with the 'main' module"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "if-statements.go"
- ],
- "sha1": "d721dbc2d0c1b003563fe79a82b9f2d3f609cc64",
- "gitDir": "test/corpus/repos/go",
- "sha2": "8ff80ea94d04e830ad846d865336e741c8364795"
-}
-,{
- "testCaseDescription": "go-if-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"if-statements.go": [
@@ -50,56 +7,11 @@
"span": {
"insert": {
"start": [
+ 1,
+ 1
+ ],
+ "end": [
3,
- 1
- ],
- "end": [
- 5,
- 2
- ]
- }
- },
- "summary": "Added the 'x()' if statement"
- },
- {
- "span": {
- "insert": {
- "start": [
- 6,
- 1
- ],
- "end": [
- 8,
- 2
- ]
- }
- },
- "summary": "Added the 'y := b(); c' if statement"
- },
- {
- "span": {
- "insert": {
- "start": [
- 9,
- 1
- ],
- "end": [
- 13,
- 2
- ]
- }
- },
- "summary": "Added the 'z()' if statement"
- },
- {
- "span": {
- "insert": {
- "start": [
- 14,
- 1
- ],
- "end": [
- 16,
2
]
}
@@ -110,11 +22,11 @@
"span": {
"insert": {
"start": [
- 17,
+ 4,
1
],
"end": [
- 19,
+ 6,
2
]
}
@@ -125,11 +37,11 @@
"span": {
"insert": {
"start": [
- 20,
+ 7,
1
],
"end": [
- 24,
+ 11,
2
]
}
@@ -143,9 +55,163 @@
"filePaths": [
"if-statements.go"
],
- "sha1": "8ff80ea94d04e830ad846d865336e741c8364795",
+ "patch": [
+ "diff --git a/if-statements.go b/if-statements.go",
+ "index e69de29..2266b8b 100644",
+ "--- a/if-statements.go",
+ "+++ b/if-statements.go",
+ "@@ -0,0 +1,11 @@",
+ "+if a() {",
+ "+b()",
+ "+}",
+ "+if a := b(); c {",
+ "+d()",
+ "+}",
+ "+if a() {",
+ "+b()",
+ "+} else {",
+ "+c()",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "184deca8ba9943201f8512be5ff7f986db1bd6ac"
+ "shas": "bd35724ed7512ba9bb228b806e5888f347bd3793..eae64fa16d42245a11d166f1bd836ed97eeb419d"
+}
+,{
+ "testCaseDescription": "go-if-statements-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "if-statements.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'x()' if statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'y := b(); c' if statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 11,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'z()' if statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 12,
+ 1
+ ],
+ "end": [
+ 14,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'a()' if statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 15,
+ 1
+ ],
+ "end": [
+ 17,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'a := b(); c' if statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 18,
+ 1
+ ],
+ "end": [
+ 22,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'a()' if statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "if-statements.go"
+ ],
+ "patch": [
+ "diff --git a/if-statements.go b/if-statements.go",
+ "index 2266b8b..abacd6e 100644",
+ "--- a/if-statements.go",
+ "+++ b/if-statements.go",
+ "@@ -1,3 +1,25 @@",
+ "+if x() {",
+ "+b()",
+ "+}",
+ "+if y := b(); c {",
+ "+d()",
+ "+}",
+ "+if z() {",
+ "+b()",
+ "+} else {",
+ "+c()",
+ "+}",
+ "+if a() {",
+ "+b()",
+ "+}",
+ "+if a := b(); c {",
+ "+d()",
+ "+}",
+ "+if a() {",
+ "+b()",
+ "+} else {",
+ "+c()",
+ "+}",
+ " if a() {",
+ " b()",
+ " }"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "eae64fa16d42245a11d166f1bd836ed97eeb419d..409746cfde8f39fbd3a12243a73b81846da41749"
}
,{
"testCaseDescription": "go-if-statements-delete-insert-test",
@@ -157,21 +223,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
},
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -184,21 +250,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
},
{
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -211,21 +277,21 @@
"replace": [
{
"start": [
- 9,
+ 7,
4
],
"end": [
- 9,
+ 7,
5
]
},
{
"start": [
- 9,
+ 7,
4
],
"end": [
- 9,
+ 7,
5
]
}
@@ -240,9 +306,28 @@
"filePaths": [
"if-statements.go"
],
- "sha1": "184deca8ba9943201f8512be5ff7f986db1bd6ac",
+ "patch": [
+ "diff --git a/if-statements.go b/if-statements.go",
+ "index abacd6e..b5fd21a 100644",
+ "--- a/if-statements.go",
+ "+++ b/if-statements.go",
+ "@@ -1,10 +1,10 @@",
+ "-if x() {",
+ "+if a() {",
+ " b()",
+ " }",
+ "-if y := b(); c {",
+ "+if a := b(); c {",
+ " d()",
+ " }",
+ "-if z() {",
+ "+if a() {",
+ " b()",
+ " } else {",
+ " c()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "1068ba7d4a382ce159ece211090eb64635d01d6f"
+ "shas": "409746cfde8f39fbd3a12243a73b81846da41749..56ba51da2e8ad7a81adbcd1e3a5fc413ea01b591"
}
,{
"testCaseDescription": "go-if-statements-replacement-test",
@@ -254,21 +339,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
},
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -281,21 +366,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
},
{
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -308,21 +393,21 @@
"replace": [
{
"start": [
- 9,
+ 7,
4
],
"end": [
- 9,
+ 7,
5
]
},
{
"start": [
- 9,
+ 7,
4
],
"end": [
- 9,
+ 7,
5
]
}
@@ -337,9 +422,28 @@
"filePaths": [
"if-statements.go"
],
- "sha1": "1068ba7d4a382ce159ece211090eb64635d01d6f",
+ "patch": [
+ "diff --git a/if-statements.go b/if-statements.go",
+ "index b5fd21a..abacd6e 100644",
+ "--- a/if-statements.go",
+ "+++ b/if-statements.go",
+ "@@ -1,10 +1,10 @@",
+ "-if a() {",
+ "+if x() {",
+ " b()",
+ " }",
+ "-if a := b(); c {",
+ "+if y := b(); c {",
+ " d()",
+ " }",
+ "-if a() {",
+ "+if z() {",
+ " b()",
+ " } else {",
+ " c()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "30bf2cf7b32f74fcb2eeeee6582adfff52d0f7f7"
+ "shas": "56ba51da2e8ad7a81adbcd1e3a5fc413ea01b591..876916554c152592cefc38a8f9a9e265f24fea7b"
}
,{
"testCaseDescription": "go-if-statements-delete-replacement-test",
@@ -350,11 +454,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -365,11 +469,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -380,11 +484,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 13,
+ 11,
2
]
}
@@ -395,11 +499,11 @@
"span": {
"delete": {
"start": [
- 14,
+ 12,
1
],
"end": [
- 16,
+ 14,
2
]
}
@@ -410,11 +514,11 @@
"span": {
"delete": {
"start": [
- 17,
+ 15,
1
],
"end": [
- 19,
+ 17,
2
]
}
@@ -425,11 +529,11 @@
"span": {
"delete": {
"start": [
- 20,
+ 18,
1
],
"end": [
- 24,
+ 22,
2
]
}
@@ -440,11 +544,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 12,
1
],
"end": [
- 16,
+ 14,
2
]
}
@@ -455,11 +559,11 @@
"span": {
"insert": {
"start": [
- 17,
+ 15,
1
],
"end": [
- 19,
+ 17,
2
]
}
@@ -470,11 +574,11 @@
"span": {
"insert": {
"start": [
- 20,
+ 18,
1
],
"end": [
- 24,
+ 22,
2
]
}
@@ -488,9 +592,46 @@
"filePaths": [
"if-statements.go"
],
- "sha1": "30bf2cf7b32f74fcb2eeeee6582adfff52d0f7f7",
+ "patch": [
+ "diff --git a/if-statements.go b/if-statements.go",
+ "index abacd6e..ccb09fd 100644",
+ "--- a/if-statements.go",
+ "+++ b/if-statements.go",
+ "@@ -1,14 +1,3 @@",
+ "-if x() {",
+ "-b()",
+ "-}",
+ "-if y := b(); c {",
+ "-d()",
+ "-}",
+ "-if z() {",
+ "-b()",
+ "-} else {",
+ "-c()",
+ "-}",
+ " if a() {",
+ " b()",
+ " }",
+ "@@ -20,13 +9,13 @@ b()",
+ " } else {",
+ " c()",
+ " }",
+ "-if a() {",
+ "+if x() {",
+ " b()",
+ " }",
+ "-if a := b(); c {",
+ "+if y := b(); c {",
+ " d()",
+ " }",
+ "-if a() {",
+ "+if z() {",
+ " b()",
+ " } else {",
+ " c()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "944d39dd78c1bfad643bf098aff846ff74368f41"
+ "shas": "876916554c152592cefc38a8f9a9e265f24fea7b..df039b5f947ac9e901fd47d32263ba46ccc9a518"
}
,{
"testCaseDescription": "go-if-statements-delete-test",
@@ -501,11 +642,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -516,11 +657,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -531,11 +672,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 13,
+ 11,
2
]
}
@@ -549,9 +690,29 @@
"filePaths": [
"if-statements.go"
],
- "sha1": "944d39dd78c1bfad643bf098aff846ff74368f41",
+ "patch": [
+ "diff --git a/if-statements.go b/if-statements.go",
+ "index ccb09fd..2e63573 100644",
+ "--- a/if-statements.go",
+ "+++ b/if-statements.go",
+ "@@ -1,14 +1,3 @@",
+ "-if a() {",
+ "-b()",
+ "-}",
+ "-if a := b(); c {",
+ "-d()",
+ "-}",
+ "-if a() {",
+ "-b()",
+ "-} else {",
+ "-c()",
+ "-}",
+ " if x() {",
+ " b()",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e9ce6c61402f2e5b5b6a18eb58248f7108645a98"
+ "shas": "df039b5f947ac9e901fd47d32263ba46ccc9a518..07a2bf60cdec6bbf5cf0ffc5e10c6695b03ae176"
}
,{
"testCaseDescription": "go-if-statements-delete-rest-test",
@@ -560,30 +721,48 @@
"if-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'x()' if statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'y := b(); c' if statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 11,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'z()' if statement"
}
]
},
@@ -592,7 +771,24 @@
"filePaths": [
"if-statements.go"
],
- "sha1": "e9ce6c61402f2e5b5b6a18eb58248f7108645a98",
+ "patch": [
+ "diff --git a/if-statements.go b/if-statements.go",
+ "index 2e63573..e69de29 100644",
+ "--- a/if-statements.go",
+ "+++ b/if-statements.go",
+ "@@ -1,11 +0,0 @@",
+ "-if x() {",
+ "-b()",
+ "-}",
+ "-if y := b(); c {",
+ "-d()",
+ "-}",
+ "-if z() {",
+ "-b()",
+ "-} else {",
+ "-c()",
+ "-}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c960fcc65ac55182c76b10f2b295a3cc10166860"
+ "shas": "07a2bf60cdec6bbf5cf0ffc5e10c6695b03ae176..294f5cc0ef0e25ecf0309fd41ae6cd4b376ab627"
}]
diff --git a/test/corpus/diff-summaries/go/imaginary-literals.json b/test/corpus/diff-summaries/go/imaginary-literals.json
index 5540a5bc1..dc90ad3a6 100644
--- a/test/corpus/diff-summaries/go/imaginary-literals.json
+++ b/test/corpus/diff-summaries/go/imaginary-literals.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -40,9 +40,19 @@
"filePaths": [
"imaginary-literals.go"
],
- "sha1": "6a5c5e925499fc0ac05bc20d3440592bebc89ea5",
+ "patch": [
+ "diff --git a/imaginary-literals.go b/imaginary-literals.go",
+ "index e69de29..aca2d55 100644",
+ "--- a/imaginary-literals.go",
+ "+++ b/imaginary-literals.go",
+ "@@ -0,0 +1,4 @@",
+ "+const (",
+ "+a = 01i",
+ "+b = 1.e+100i",
+ "+)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "04ef00437176d8193e549a700e3b19929002cc76"
+ "shas": "6761a7543f7002279b3e1d53f388c0b6408e11ac..70a8f336ad4cf76dbf55d755ee3b4ff94b77dc5b"
}
,{
"testCaseDescription": "go-imaginary-literals-replacement-insert-test",
@@ -53,11 +63,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -68,11 +78,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -83,11 +93,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -98,11 +108,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -116,9 +126,27 @@
"filePaths": [
"imaginary-literals.go"
],
- "sha1": "04ef00437176d8193e549a700e3b19929002cc76",
+ "patch": [
+ "diff --git a/imaginary-literals.go b/imaginary-literals.go",
+ "index aca2d55..6983988 100644",
+ "--- a/imaginary-literals.go",
+ "+++ b/imaginary-literals.go",
+ "@@ -1,4 +1,12 @@",
+ " const (",
+ "+a = 02i",
+ "+b = 1.e+103i",
+ "+)",
+ "+const (",
+ "+a = 01i",
+ "+b = 1.e+100i",
+ "+)",
+ "+const (",
+ " a = 01i",
+ " b = 1.e+100i",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "60b55b83363314517314e8c074c54c9244ac20ad"
+ "shas": "70a8f336ad4cf76dbf55d755ee3b4ff94b77dc5b..7003c23d83606920ba4dbc36a6fa8aa3fb23d254"
}
,{
"testCaseDescription": "go-imaginary-literals-delete-insert-test",
@@ -130,54 +158,54 @@
"replace": [
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
}
]
},
- "summary": "Replaced the '02i' imaginary_literal with the '01i' imaginary_literal in the a variable of the 'main' module"
+ "summary": "Replaced the '02i' imaginary_literal with the '01i' imaginary_literal in the a variable"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
13
]
},
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
13
]
}
]
},
- "summary": "Replaced the '1.e+103i' imaginary_literal with the '1.e+100i' imaginary_literal in the b variable of the 'main' module"
+ "summary": "Replaced the '1.e+103i' imaginary_literal with the '1.e+100i' imaginary_literal in the b variable"
}
]
},
@@ -186,9 +214,23 @@
"filePaths": [
"imaginary-literals.go"
],
- "sha1": "60b55b83363314517314e8c074c54c9244ac20ad",
+ "patch": [
+ "diff --git a/imaginary-literals.go b/imaginary-literals.go",
+ "index 6983988..a7e36a5 100644",
+ "--- a/imaginary-literals.go",
+ "+++ b/imaginary-literals.go",
+ "@@ -1,6 +1,6 @@",
+ " const (",
+ "-a = 02i",
+ "-b = 1.e+103i",
+ "+a = 01i",
+ "+b = 1.e+100i",
+ " )",
+ " const (",
+ " a = 01i"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "95e686a3b779e865259de5a05c7284342ec9efe5"
+ "shas": "7003c23d83606920ba4dbc36a6fa8aa3fb23d254..9c8a6f328131e0ab48ab9cccdf3a8a0ab164e527"
}
,{
"testCaseDescription": "go-imaginary-literals-replacement-test",
@@ -200,54 +242,54 @@
"replace": [
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
}
]
},
- "summary": "Replaced the '01i' imaginary_literal with the '02i' imaginary_literal in the a variable of the 'main' module"
+ "summary": "Replaced the '01i' imaginary_literal with the '02i' imaginary_literal in the a variable"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
13
]
},
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
13
]
}
]
},
- "summary": "Replaced the '1.e+100i' imaginary_literal with the '1.e+103i' imaginary_literal in the b variable of the 'main' module"
+ "summary": "Replaced the '1.e+100i' imaginary_literal with the '1.e+103i' imaginary_literal in the b variable"
}
]
},
@@ -256,9 +298,23 @@
"filePaths": [
"imaginary-literals.go"
],
- "sha1": "95e686a3b779e865259de5a05c7284342ec9efe5",
+ "patch": [
+ "diff --git a/imaginary-literals.go b/imaginary-literals.go",
+ "index a7e36a5..6983988 100644",
+ "--- a/imaginary-literals.go",
+ "+++ b/imaginary-literals.go",
+ "@@ -1,6 +1,6 @@",
+ " const (",
+ "-a = 01i",
+ "-b = 1.e+100i",
+ "+a = 02i",
+ "+b = 1.e+103i",
+ " )",
+ " const (",
+ " a = 01i"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "498a8733d663fcea7130e75224198910ad23d497"
+ "shas": "9c8a6f328131e0ab48ab9cccdf3a8a0ab164e527..06c027b6920c1d1e7f4b44cd6527798c933581c4"
}
,{
"testCaseDescription": "go-imaginary-literals-delete-replacement-test",
@@ -269,11 +325,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -284,11 +340,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -299,11 +355,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -314,11 +370,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -329,11 +385,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -344,11 +400,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -362,9 +418,29 @@
"filePaths": [
"imaginary-literals.go"
],
- "sha1": "498a8733d663fcea7130e75224198910ad23d497",
+ "patch": [
+ "diff --git a/imaginary-literals.go b/imaginary-literals.go",
+ "index 6983988..02cff8d 100644",
+ "--- a/imaginary-literals.go",
+ "+++ b/imaginary-literals.go",
+ "@@ -1,12 +1,8 @@",
+ " const (",
+ "-a = 02i",
+ "-b = 1.e+103i",
+ "-)",
+ "-const (",
+ " a = 01i",
+ " b = 1.e+100i",
+ " )",
+ " const (",
+ "-a = 01i",
+ "-b = 1.e+100i",
+ "+a = 02i",
+ "+b = 1.e+103i",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "d11becbeaabdb5e5e1eb9efb0db1b3439bc42139"
+ "shas": "06c027b6920c1d1e7f4b44cd6527798c933581c4..b6de01e92b11ca25862dcd7d798b72f9a01aa1c4"
}
,{
"testCaseDescription": "go-imaginary-literals-delete-test",
@@ -375,11 +451,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -390,11 +466,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -408,9 +484,23 @@
"filePaths": [
"imaginary-literals.go"
],
- "sha1": "d11becbeaabdb5e5e1eb9efb0db1b3439bc42139",
+ "patch": [
+ "diff --git a/imaginary-literals.go b/imaginary-literals.go",
+ "index 02cff8d..6d8ec55 100644",
+ "--- a/imaginary-literals.go",
+ "+++ b/imaginary-literals.go",
+ "@@ -1,8 +1,4 @@",
+ " const (",
+ "-a = 01i",
+ "-b = 1.e+100i",
+ "-)",
+ "-const (",
+ " a = 02i",
+ " b = 1.e+103i",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "0afc23ae41d67a623887428c19698f2051e71d09"
+ "shas": "b6de01e92b11ca25862dcd7d798b72f9a01aa1c4..8af14aaa12876d71baf9d1580b9de3a0b4769e2a"
}
,{
"testCaseDescription": "go-imaginary-literals-delete-rest-test",
@@ -421,11 +511,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -436,11 +526,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -454,7 +544,17 @@
"filePaths": [
"imaginary-literals.go"
],
- "sha1": "0afc23ae41d67a623887428c19698f2051e71d09",
+ "patch": [
+ "diff --git a/imaginary-literals.go b/imaginary-literals.go",
+ "index 6d8ec55..e69de29 100644",
+ "--- a/imaginary-literals.go",
+ "+++ b/imaginary-literals.go",
+ "@@ -1,4 +0,0 @@",
+ "-const (",
+ "-a = 02i",
+ "-b = 1.e+103i",
+ "-)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "46503417695204e939923a09702395449f526a66"
+ "shas": "8af14aaa12876d71baf9d1580b9de3a0b4769e2a..3f18376b34b25deb3740a62df8c40ad667cfef4a"
}]
diff --git a/test/corpus/diff-summaries/go/increment-decrement-statements.json b/test/corpus/diff-summaries/go/increment-decrement-statements.json
index e9730cacb..332facc5c 100644
--- a/test/corpus/diff-summaries/go/increment-decrement-statements.json
+++ b/test/corpus/diff-summaries/go/increment-decrement-statements.json
@@ -1,48 +1,5 @@
[{
"testCaseDescription": "go-increment-decrement-statements-insert-test",
- "expectedResult": {
- "changes": {
- "increment-decrement-statements.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
- },
- "summary": "Replaced the 'main' module with the 'main' module"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "increment-decrement-statements.go"
- ],
- "sha1": "353e531a55c6c3d0540570c523e799df46615898",
- "gitDir": "test/corpus/repos/go",
- "sha2": "05731f26c98d3d4cf93557f3f95192d6d97e8be5"
-}
-,{
- "testCaseDescription": "go-increment-decrement-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"increment-decrement-statements.go": [
@@ -50,41 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
- 4
- ]
- }
- },
- "summary": "Added the 'foo' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 2
- ]
- }
- },
- "summary": "Added the 'x' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 1
- ],
- "end": [
- 5,
+ 1,
2
]
}
@@ -95,11 +22,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 2,
1
],
"end": [
- 6,
+ 2,
2
]
}
@@ -113,9 +40,105 @@
"filePaths": [
"increment-decrement-statements.go"
],
- "sha1": "05731f26c98d3d4cf93557f3f95192d6d97e8be5",
+ "patch": [
+ "diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
+ "index e69de29..c118f41 100644",
+ "--- a/increment-decrement-statements.go",
+ "+++ b/increment-decrement-statements.go",
+ "@@ -0,0 +1,2 @@",
+ "+i++",
+ "+j--"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "9c9be572b7c83e36de9a5997c7987815168a6a23"
+ "shas": "acf23921d6e89772dac98a78ba280e58c2429050..74900cd980876ca3be4654c097b3ee3475d51726"
+}
+,{
+ "testCaseDescription": "go-increment-decrement-statements-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "increment-decrement-statements.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'x' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'i' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'j' identifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "increment-decrement-statements.go"
+ ],
+ "patch": [
+ "diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
+ "index c118f41..d617bc4 100644",
+ "--- a/increment-decrement-statements.go",
+ "+++ b/increment-decrement-statements.go",
+ "@@ -1,2 +1,6 @@",
+ "+foo++",
+ "+x++",
+ "+i++",
+ "+j--",
+ " i++",
+ " j--"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "74900cd980876ca3be4654c097b3ee3475d51726..141a025429562d95737cea6257998bb5f91afdc4"
}
,{
"testCaseDescription": "go-increment-decrement-statements-delete-insert-test",
@@ -127,21 +150,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
4
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -153,11 +176,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -168,11 +191,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -186,9 +209,22 @@
"filePaths": [
"increment-decrement-statements.go"
],
- "sha1": "9c9be572b7c83e36de9a5997c7987815168a6a23",
+ "patch": [
+ "diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
+ "index d617bc4..15214d0 100644",
+ "--- a/increment-decrement-statements.go",
+ "+++ b/increment-decrement-statements.go",
+ "@@ -1,5 +1,5 @@",
+ "-foo++",
+ "-x++",
+ "+i++",
+ "+j--",
+ " i++",
+ " j--",
+ " i++"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c1ef5fffc731c318afb45049a81983a54f1ad6bd"
+ "shas": "141a025429562d95737cea6257998bb5f91afdc4..8f96737bbb510f71457b32de6ff88f244261ca3a"
}
,{
"testCaseDescription": "go-increment-decrement-statements-replacement-test",
@@ -200,21 +236,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
4
]
}
@@ -226,11 +262,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -241,11 +277,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -259,9 +295,22 @@
"filePaths": [
"increment-decrement-statements.go"
],
- "sha1": "c1ef5fffc731c318afb45049a81983a54f1ad6bd",
+ "patch": [
+ "diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
+ "index 15214d0..d617bc4 100644",
+ "--- a/increment-decrement-statements.go",
+ "+++ b/increment-decrement-statements.go",
+ "@@ -1,5 +1,5 @@",
+ "-i++",
+ "-j--",
+ "+foo++",
+ "+x++",
+ " i++",
+ " j--",
+ " i++"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "494d53aa2b6983358c04d03252664e33375e204f"
+ "shas": "8f96737bbb510f71457b32de6ff88f244261ca3a..4189214ea59e379b3c40a1a079666495490968cc"
}
,{
"testCaseDescription": "go-increment-decrement-statements-delete-replacement-test",
@@ -272,11 +321,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
4
]
}
@@ -287,11 +336,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -302,11 +351,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
2
]
}
@@ -317,11 +366,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -332,11 +381,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
4
]
}
@@ -347,11 +396,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -365,9 +414,23 @@
"filePaths": [
"increment-decrement-statements.go"
],
- "sha1": "494d53aa2b6983358c04d03252664e33375e204f",
+ "patch": [
+ "diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
+ "index d617bc4..640bbf1 100644",
+ "--- a/increment-decrement-statements.go",
+ "+++ b/increment-decrement-statements.go",
+ "@@ -1,6 +1,4 @@",
+ "-foo++",
+ "-x++",
+ "-i++",
+ "-j--",
+ " i++",
+ " j--",
+ "+foo++",
+ "+x++"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a8f0122076dddd7b2ccc818bb7b6e6e7f819cacc"
+ "shas": "4189214ea59e379b3c40a1a079666495490968cc..b01ab200bee6790fce1710c34aeb967595509f86"
}
,{
"testCaseDescription": "go-increment-decrement-statements-delete-test",
@@ -378,11 +441,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -393,11 +456,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -411,9 +474,19 @@
"filePaths": [
"increment-decrement-statements.go"
],
- "sha1": "a8f0122076dddd7b2ccc818bb7b6e6e7f819cacc",
+ "patch": [
+ "diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
+ "index 640bbf1..b7c351d 100644",
+ "--- a/increment-decrement-statements.go",
+ "+++ b/increment-decrement-statements.go",
+ "@@ -1,4 +1,2 @@",
+ "-i++",
+ "-j--",
+ " foo++",
+ " x++"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ccc0273dc372b40fe71baf328c23abc7f1aaa558"
+ "shas": "b01ab200bee6790fce1710c34aeb967595509f86..c7abe86b7eb9259ab0b8cd859b857938aaacd550"
}
,{
"testCaseDescription": "go-increment-decrement-statements-delete-rest-test",
@@ -422,30 +495,33 @@
"increment-decrement-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'foo' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'x' identifier"
}
]
},
@@ -454,7 +530,15 @@
"filePaths": [
"increment-decrement-statements.go"
],
- "sha1": "ccc0273dc372b40fe71baf328c23abc7f1aaa558",
+ "patch": [
+ "diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
+ "index b7c351d..e69de29 100644",
+ "--- a/increment-decrement-statements.go",
+ "+++ b/increment-decrement-statements.go",
+ "@@ -1,2 +0,0 @@",
+ "-foo++",
+ "-x++"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "07104070f6fbb41df4ca2bfb623637db5ce223eb"
+ "shas": "c7abe86b7eb9259ab0b8cd859b857938aaacd550..8b892c06025823500a32131e0005fe5ea0511bd9"
}]
diff --git a/test/corpus/diff-summaries/go/indexing-expressions.json b/test/corpus/diff-summaries/go/indexing-expressions.json
index ad4f9752b..abc74970d 100644
--- a/test/corpus/diff-summaries/go/indexing-expressions.json
+++ b/test/corpus/diff-summaries/go/indexing-expressions.json
@@ -1,48 +1,5 @@
[{
"testCaseDescription": "go-indexing-expressions-insert-test",
- "expectedResult": {
- "changes": {
- "indexing-expressions.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
- },
- "summary": "Replaced the 'main' module with the 'main' module"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "indexing-expressions.go"
- ],
- "sha1": "7a0e56fcfbef48bf43e71d2d33c4b74a2cf05cb5",
- "gitDir": "test/corpus/repos/go",
- "sha2": "b44d19f6acfc5bbf67f6886339ea690f4d07fc49"
-}
-,{
- "testCaseDescription": "go-indexing-expressions-replacement-insert-test",
"expectedResult": {
"changes": {
"indexing-expressions.go": [
@@ -50,251 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
- 2
- ]
- }
- },
- "summary": "Added 'z' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 3,
- 4
- ],
- "end": [
- 3,
- 5
- ]
- }
- },
- "summary": "Added '2'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 2
- ],
- "end": [
- 4,
- 3
- ]
- }
- },
- "summary": "Added 'y' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 5
- ],
- "end": [
- 4,
- 6
- ]
- }
- },
- "summary": "Added '1'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 2
- ],
- "end": [
- 5,
- 3
- ]
- }
- },
- "summary": "Added 'x' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 4
- ],
- "end": [
- 5,
- 5
- ]
- }
- },
- "summary": "Added '1'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 6,
- 2
- ],
- "end": [
- 6,
- 3
- ]
- }
- },
- "summary": "Added 'd' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 6,
- 4
- ],
- "end": [
- 6,
- 5
- ]
- }
- },
- "summary": "Added '1'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 6,
- 6
- ],
- "end": [
- 6,
- 7
- ]
- }
- },
- "summary": "Added '2'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 7,
- 2
- ],
- "end": [
- 7,
- 3
- ]
- }
- },
- "summary": "Added 'e' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 7,
- 5
- ],
- "end": [
- 7,
- 6
- ]
- }
- },
- "summary": "Added '2'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 7,
- 7
- ],
- "end": [
- 7,
- 8
- ]
- }
- },
- "summary": "Added '3'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 2
- ],
- "end": [
- 8,
- 3
- ]
- }
- },
- "summary": "Added 'f' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 4
- ],
- "end": [
- 8,
- 5
- ]
- }
- },
- "summary": "Added '1'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 6
- ],
- "end": [
- 8,
- 7
- ]
- }
- },
- "summary": "Added '2'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 8
- ],
- "end": [
- 8,
- 9
- ]
- }
- },
- "summary": "Added '3'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 9,
- 1
- ],
- "end": [
- 9,
+ 1,
2
]
}
@@ -305,11 +22,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 1,
3
],
"end": [
- 9,
+ 1,
4
]
}
@@ -320,26 +37,26 @@
"span": {
"insert": {
"start": [
- 10,
+ 2,
2
],
"end": [
- 10,
+ 2,
3
]
}
},
- "summary": "Added the 'b' identifier"
+ "summary": "Added 'b' identifier"
},
{
"span": {
"insert": {
"start": [
- 11,
+ 3,
2
],
"end": [
- 11,
+ 3,
3
]
}
@@ -350,11 +67,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 3,
4
],
"end": [
- 11,
+ 3,
5
]
}
@@ -365,11 +82,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 4,
2
],
"end": [
- 12,
+ 4,
3
]
}
@@ -380,11 +97,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 4,
4
],
"end": [
- 12,
+ 4,
5
]
}
@@ -395,11 +112,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 4,
6
],
"end": [
- 12,
+ 4,
7
]
}
@@ -410,11 +127,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 5,
2
],
"end": [
- 13,
+ 5,
3
]
}
@@ -425,11 +142,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 5,
5
],
"end": [
- 13,
+ 5,
6
]
}
@@ -440,11 +157,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 5,
7
],
"end": [
- 13,
+ 5,
8
]
}
@@ -455,11 +172,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 6,
2
],
"end": [
- 14,
+ 6,
3
]
}
@@ -470,11 +187,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 6,
4
],
"end": [
- 14,
+ 6,
5
]
}
@@ -485,11 +202,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 6,
6
],
"end": [
- 14,
+ 6,
7
]
}
@@ -500,11 +217,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 6,
8
],
"end": [
- 14,
+ 6,
9
]
}
@@ -518,12 +235,24 @@
"filePaths": [
"indexing-expressions.go"
],
- "sha1": "b44d19f6acfc5bbf67f6886339ea690f4d07fc49",
+ "patch": [
+ "diff --git a/indexing-expressions.go b/indexing-expressions.go",
+ "index e69de29..7e17ae1 100644",
+ "--- a/indexing-expressions.go",
+ "+++ b/indexing-expressions.go",
+ "@@ -0,0 +1,6 @@",
+ "+a[1]",
+ "+ b[:]",
+ "+ c[1:]",
+ "+ d[1:2]",
+ "+ e[:2:3]",
+ "+ f[1:2:3]"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "fe41e0eb66aad5a1df8f5ffdf95e876d0175ffba"
+ "shas": "5d7acec54aeae4a86833f9a0b00bf588083883ab..50a00fd11c16a7acef5eb1edf28f295060d8d978"
}
,{
- "testCaseDescription": "go-indexing-expressions-delete-insert-test",
+ "testCaseDescription": "go-indexing-expressions-replacement-insert-test",
"expectedResult": {
"changes": {
"indexing-expressions.go": [
@@ -531,27 +260,87 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
},
- "summary": "Added 'a' identifier"
+ "summary": "Added 'z' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 4
+ ],
+ "end": [
+ 1,
+ 5
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 2
+ ],
+ "end": [
+ 2,
+ 3
+ ]
+ }
+ },
+ "summary": "Added 'y' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ },
+ "summary": "Added '1'"
},
{
"span": {
"insert": {
"start": [
3,
- 3
+ 2
],
"end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Added 'x' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
3,
4
+ ],
+ "end": [
+ 3,
+ 5
]
}
},
@@ -570,6 +359,448 @@
]
}
},
+ "summary": "Added 'd' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 4
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Added '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 6
+ ],
+ "end": [
+ 4,
+ 7
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 2
+ ],
+ "end": [
+ 5,
+ 3
+ ]
+ }
+ },
+ "summary": "Added 'e' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 5,
+ 6
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 7
+ ],
+ "end": [
+ 5,
+ 8
+ ]
+ }
+ },
+ "summary": "Added '3'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 2
+ ],
+ "end": [
+ 6,
+ 3
+ ]
+ }
+ },
+ "summary": "Added 'f' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 4
+ ],
+ "end": [
+ 6,
+ 5
+ ]
+ }
+ },
+ "summary": "Added '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 6
+ ],
+ "end": [
+ 6,
+ 7
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 8
+ ],
+ "end": [
+ 6,
+ 9
+ ]
+ }
+ },
+ "summary": "Added '3'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ }
+ },
+ "summary": "Added 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 3
+ ],
+ "end": [
+ 7,
+ 4
+ ]
+ }
+ },
+ "summary": "Added '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 2
+ ],
+ "end": [
+ 8,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 2
+ ],
+ "end": [
+ 9,
+ 3
+ ]
+ }
+ },
+ "summary": "Added 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 4
+ ],
+ "end": [
+ 9,
+ 5
+ ]
+ }
+ },
+ "summary": "Added '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 10,
+ 2
+ ],
+ "end": [
+ 10,
+ 3
+ ]
+ }
+ },
+ "summary": "Added 'd' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 10,
+ 4
+ ],
+ "end": [
+ 10,
+ 5
+ ]
+ }
+ },
+ "summary": "Added '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 10,
+ 6
+ ],
+ "end": [
+ 10,
+ 7
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 11,
+ 2
+ ],
+ "end": [
+ 11,
+ 3
+ ]
+ }
+ },
+ "summary": "Added 'e' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 11,
+ 5
+ ],
+ "end": [
+ 11,
+ 6
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 11,
+ 7
+ ],
+ "end": [
+ 11,
+ 8
+ ]
+ }
+ },
+ "summary": "Added '3'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 12,
+ 2
+ ],
+ "end": [
+ 12,
+ 3
+ ]
+ }
+ },
+ "summary": "Added 'f' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 12,
+ 4
+ ],
+ "end": [
+ 12,
+ 5
+ ]
+ }
+ },
+ "summary": "Added '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 12,
+ 6
+ ],
+ "end": [
+ 12,
+ 7
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 12,
+ 8
+ ],
+ "end": [
+ 12,
+ 9
+ ]
+ }
+ },
+ "summary": "Added '3'"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "indexing-expressions.go"
+ ],
+ "patch": [
+ "diff --git a/indexing-expressions.go b/indexing-expressions.go",
+ "index 7e17ae1..4b30922 100644",
+ "--- a/indexing-expressions.go",
+ "+++ b/indexing-expressions.go",
+ "@@ -1,3 +1,15 @@",
+ "+z[:2]",
+ "+ y[:1]",
+ "+ x[1:]",
+ "+ d[1:2]",
+ "+ e[:2:3]",
+ "+ f[1:2:3]",
+ "+a[1]",
+ "+ b[:]",
+ "+ c[1:]",
+ "+ d[1:2]",
+ "+ e[:2:3]",
+ "+ f[1:2:3]",
+ " a[1]",
+ " b[:]",
+ " c[1:]"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "50a00fd11c16a7acef5eb1edf28f295060d8d978..c3ebd1a2cc9d28d6e07e53942f979108de0dcb99"
+}
+,{
+ "testCaseDescription": "go-indexing-expressions-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "indexing-expressions.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 2
+ ]
+ }
+ },
+ "summary": "Added 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 3
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
+ },
+ "summary": "Added '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 2
+ ],
+ "end": [
+ 2,
+ 3
+ ]
+ }
+ },
"summary": "Added the 'b' identifier"
},
{
@@ -577,21 +808,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
},
{
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -604,21 +835,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
},
{
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -630,11 +861,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
3
]
}
@@ -645,11 +876,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
}
@@ -660,11 +891,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -675,11 +906,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -693,9 +924,24 @@
"filePaths": [
"indexing-expressions.go"
],
- "sha1": "fe41e0eb66aad5a1df8f5ffdf95e876d0175ffba",
+ "patch": [
+ "diff --git a/indexing-expressions.go b/indexing-expressions.go",
+ "index 4b30922..f5fa086 100644",
+ "--- a/indexing-expressions.go",
+ "+++ b/indexing-expressions.go",
+ "@@ -1,6 +1,6 @@",
+ "-z[:2]",
+ "- y[:1]",
+ "- x[1:]",
+ "+a[1]",
+ "+ b[:]",
+ "+ c[1:]",
+ " d[1:2]",
+ " e[:2:3]",
+ " f[1:2:3]"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "198518baec67c944e513ebc65d82c6ffde6542b8"
+ "shas": "c3ebd1a2cc9d28d6e07e53942f979108de0dcb99..6f976f7892d6877ce2f476e36a2048efce51984c"
}
,{
"testCaseDescription": "go-indexing-expressions-replacement-test",
@@ -706,11 +952,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -721,11 +967,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -736,11 +982,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
3
]
}
@@ -751,11 +997,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
}
@@ -766,11 +1012,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -781,11 +1027,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -796,11 +1042,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -811,11 +1057,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -826,11 +1072,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
3
]
}
@@ -841,11 +1087,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -856,11 +1102,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -874,9 +1120,24 @@
"filePaths": [
"indexing-expressions.go"
],
- "sha1": "198518baec67c944e513ebc65d82c6ffde6542b8",
+ "patch": [
+ "diff --git a/indexing-expressions.go b/indexing-expressions.go",
+ "index f5fa086..4b30922 100644",
+ "--- a/indexing-expressions.go",
+ "+++ b/indexing-expressions.go",
+ "@@ -1,6 +1,6 @@",
+ "-a[1]",
+ "- b[:]",
+ "- c[1:]",
+ "+z[:2]",
+ "+ y[:1]",
+ "+ x[1:]",
+ " d[1:2]",
+ " e[:2:3]",
+ " f[1:2:3]"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c2eab21985363577dad0d08638c5060ab80a8e25"
+ "shas": "6f976f7892d6877ce2f476e36a2048efce51984c..adbbad198d55a06a1c023b30181b50d4d62f94d9"
}
,{
"testCaseDescription": "go-indexing-expressions-delete-replacement-test",
@@ -887,11 +1148,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -902,11 +1163,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -917,11 +1178,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
3
]
}
@@ -932,11 +1193,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
}
@@ -947,11 +1208,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -962,11 +1223,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -977,11 +1238,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
3
]
}
@@ -992,11 +1253,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -1007,11 +1268,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -1022,11 +1283,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
2
],
"end": [
- 7,
+ 5,
3
]
}
@@ -1037,11 +1298,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
6
]
}
@@ -1052,11 +1313,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
7
],
"end": [
- 7,
+ 5,
8
]
}
@@ -1067,11 +1328,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
2
],
"end": [
- 8,
+ 6,
3
]
}
@@ -1082,11 +1343,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
4
],
"end": [
- 8,
+ 6,
5
]
}
@@ -1097,11 +1358,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
7
]
}
@@ -1112,11 +1373,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
8
],
"end": [
- 8,
+ 6,
9
]
}
@@ -1127,11 +1388,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
2
]
}
@@ -1142,11 +1403,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
4
],
"end": [
- 9,
+ 7,
5
]
}
@@ -1157,11 +1418,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
2
],
"end": [
- 10,
+ 8,
3
]
}
@@ -1172,11 +1433,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
5
],
"end": [
- 10,
+ 8,
6
]
}
@@ -1187,11 +1448,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
2
],
"end": [
- 11,
+ 9,
3
]
}
@@ -1202,11 +1463,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
4
],
"end": [
- 11,
+ 9,
5
]
}
@@ -1217,11 +1478,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
1
],
"end": [
- 15,
+ 13,
2
]
}
@@ -1232,11 +1493,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
3
],
"end": [
- 15,
+ 13,
4
]
}
@@ -1247,11 +1508,11 @@
"span": {
"delete": {
"start": [
- 16,
+ 14,
2
],
"end": [
- 16,
+ 14,
3
]
}
@@ -1262,11 +1523,11 @@
"span": {
"delete": {
"start": [
- 17,
+ 15,
2
],
"end": [
- 17,
+ 15,
3
]
}
@@ -1277,11 +1538,11 @@
"span": {
"delete": {
"start": [
- 17,
+ 15,
4
],
"end": [
- 17,
+ 15,
5
]
}
@@ -1295,9 +1556,36 @@
"filePaths": [
"indexing-expressions.go"
],
- "sha1": "c2eab21985363577dad0d08638c5060ab80a8e25",
+ "patch": [
+ "diff --git a/indexing-expressions.go b/indexing-expressions.go",
+ "index 4b30922..06ae51b 100644",
+ "--- a/indexing-expressions.go",
+ "+++ b/indexing-expressions.go",
+ "@@ -1,18 +1,12 @@",
+ "-z[:2]",
+ "- y[:1]",
+ "- x[1:]",
+ "- d[1:2]",
+ "- e[:2:3]",
+ "- f[1:2:3]",
+ " a[1]",
+ " b[:]",
+ " c[1:]",
+ " d[1:2]",
+ " e[:2:3]",
+ " f[1:2:3]",
+ "-a[1]",
+ "- b[:]",
+ "- c[1:]",
+ "+z[:2]",
+ "+ y[:1]",
+ "+ x[1:]",
+ " d[1:2]",
+ " e[:2:3]",
+ " f[1:2:3]"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "076c02eb4827aba2c39dc79d8866d1b4136c769e"
+ "shas": "adbbad198d55a06a1c023b30181b50d4d62f94d9..a230c61f683ae85deb15870f107311a252b01a41"
}
,{
"testCaseDescription": "go-indexing-expressions-delete-test",
@@ -1308,11 +1596,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -1323,11 +1611,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -1338,11 +1626,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
3
]
}
@@ -1353,11 +1641,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -1368,11 +1656,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -1383,11 +1671,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
3
]
}
@@ -1398,11 +1686,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -1413,11 +1701,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -1428,11 +1716,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
2
],
"end": [
- 7,
+ 5,
3
]
}
@@ -1443,11 +1731,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
6
]
}
@@ -1458,11 +1746,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
7
],
"end": [
- 7,
+ 5,
8
]
}
@@ -1473,11 +1761,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
2
],
"end": [
- 8,
+ 6,
3
]
}
@@ -1488,11 +1776,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
4
],
"end": [
- 8,
+ 6,
5
]
}
@@ -1503,11 +1791,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
7
]
}
@@ -1518,11 +1806,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
8
],
"end": [
- 8,
+ 6,
9
]
}
@@ -1536,9 +1824,24 @@
"filePaths": [
"indexing-expressions.go"
],
- "sha1": "076c02eb4827aba2c39dc79d8866d1b4136c769e",
+ "patch": [
+ "diff --git a/indexing-expressions.go b/indexing-expressions.go",
+ "index 06ae51b..920a809 100644",
+ "--- a/indexing-expressions.go",
+ "+++ b/indexing-expressions.go",
+ "@@ -1,9 +1,3 @@",
+ "-a[1]",
+ "- b[:]",
+ "- c[1:]",
+ "- d[1:2]",
+ "- e[:2:3]",
+ "- f[1:2:3]",
+ " z[:2]",
+ " y[:1]",
+ " x[1:]"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "760d60991b3e9d36763fe9115f4162a5b01f40ec"
+ "shas": "a230c61f683ae85deb15870f107311a252b01a41..cd094c98b6f9cd8fe17a096aad0d9c96b783b2fc"
}
,{
"testCaseDescription": "go-indexing-expressions-delete-rest-test",
@@ -1547,30 +1850,243 @@
"indexing-expressions.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 2
+ ]
+ }
},
- "summary": "Replaced 'main' module with 'main' module"
+ "summary": "Deleted 'z' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 4
+ ],
+ "end": [
+ 1,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted '2'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 2
+ ],
+ "end": [
+ 2,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted 'y' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted '1'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 2
+ ],
+ "end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted 'x' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 4
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted '1'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 2
+ ],
+ "end": [
+ 4,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted 'd' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 4
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted '1'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 6
+ ],
+ "end": [
+ 4,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted '2'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 2
+ ],
+ "end": [
+ 5,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted 'e' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 5,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted '2'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 7
+ ],
+ "end": [
+ 5,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted '3'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 2
+ ],
+ "end": [
+ 6,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted 'f' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 4
+ ],
+ "end": [
+ 6,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted '1'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 6
+ ],
+ "end": [
+ 6,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted '2'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 8
+ ],
+ "end": [
+ 6,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted '3'"
}
]
},
@@ -1579,7 +2095,19 @@
"filePaths": [
"indexing-expressions.go"
],
- "sha1": "760d60991b3e9d36763fe9115f4162a5b01f40ec",
+ "patch": [
+ "diff --git a/indexing-expressions.go b/indexing-expressions.go",
+ "index 920a809..e69de29 100644",
+ "--- a/indexing-expressions.go",
+ "+++ b/indexing-expressions.go",
+ "@@ -1,6 +0,0 @@",
+ "-z[:2]",
+ "- y[:1]",
+ "- x[1:]",
+ "- d[1:2]",
+ "- e[:2:3]",
+ "- f[1:2:3]"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b1669d02e282b6c97db8719b314b3fc45b149496"
+ "shas": "cd094c98b6f9cd8fe17a096aad0d9c96b783b2fc..d3f3af3265adb9413a11a3528b28667b0c70a1e2"
}]
diff --git a/test/corpus/diff-summaries/go/int-literals.json b/test/corpus/diff-summaries/go/int-literals.json
index b23b6ed23..e3d5722b5 100644
--- a/test/corpus/diff-summaries/go/int-literals.json
+++ b/test/corpus/diff-summaries/go/int-literals.json
@@ -7,31 +7,91 @@
"span": {
"insert": {
"start": [
- 3,
+ 2,
1
],
"end": [
- 5,
+ 2,
2
]
}
},
- "summary": "Added the 'identifier' variable"
+ "summary": "Added 'a' identifier"
},
{
"span": {
"insert": {
"start": [
- 3,
- 1
+ 2,
+ 5
],
"end": [
- 5,
- 2
+ 2,
+ 6
]
}
},
- "summary": "Added the 'number' variable"
+ "summary": "Added '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 8
+ ],
+ "end": [
+ 2,
+ 9
+ ]
+ }
+ },
+ "summary": "Added 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 15
+ ],
+ "end": [
+ 2,
+ 16
+ ]
+ }
+ },
+ "summary": "Added 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 19
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ }
+ },
+ "summary": "Added '3'"
}
]
},
@@ -40,20 +100,113 @@
"filePaths": [
"int-literals.go"
],
- "sha1": "7d873f0d5579c52294d6b425bd5d9729ac1782e1",
+ "patch": [
+ "diff --git a/int-literals.go b/int-literals.go",
+ "index e69de29..11caaee 100644",
+ "--- a/int-literals.go",
+ "+++ b/int-literals.go",
+ "@@ -0,0 +1,3 @@",
+ "+const (",
+ "+a = 1, b = 2, c = 3",
+ "+)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "58e397a91e98116eca2623f4194a33e9b3a8a96b"
+ "shas": "c6aae7f905be036e251d244801d3fd73b49f6c46..5a8ab389323c7a93aca3b7eef89d2b2d2d6f6ff9"
}
,{
"testCaseDescription": "go-int-literals-replacement-insert-test",
"expectedResult": {
"changes": {
"int-literals.go": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ },
+ {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced '1' with '4'"
+ },
{
"span": {
"insert": {
"start": [
- 3,
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Added '5'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted '2'"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 2,
+ 19
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ },
+ {
+ "start": [
+ 2,
+ 19
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced '3' with '6'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
1
],
"end": [
@@ -62,52 +215,97 @@
]
}
},
- "summary": "Added the 'identifier' variable"
+ "summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
- 3,
- 1
+ 5,
+ 5
],
"end": [
5,
- 2
+ 6
]
}
},
- "summary": "Added the 'number' variable"
+ "summary": "Added the '1'"
},
{
"span": {
"insert": {
"start": [
- 6,
- 1
+ 5,
+ 8
],
"end": [
- 8,
- 2
+ 5,
+ 9
]
}
},
- "summary": "Added the 'identifier' variable"
+ "summary": "Added the 'b' identifier"
},
{
"span": {
"insert": {
"start": [
- 6,
+ 5,
+ 12
+ ],
+ "end": [
+ 5,
+ 13
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 15
+ ],
+ "end": [
+ 5,
+ 16
+ ]
+ }
+ },
+ "summary": "Added 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 19
+ ],
+ "end": [
+ 5,
+ 20
+ ]
+ }
+ },
+ "summary": "Added '3'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
1
],
"end": [
- 8,
+ 9,
2
]
}
},
- "summary": "Added the 'number' variable"
+ "summary": "Added the 'a' variable"
}
]
},
@@ -116,9 +314,24 @@
"filePaths": [
"int-literals.go"
],
- "sha1": "58e397a91e98116eca2623f4194a33e9b3a8a96b",
+ "patch": [
+ "diff --git a/int-literals.go b/int-literals.go",
+ "index 11caaee..c8fc4e8 100644",
+ "--- a/int-literals.go",
+ "+++ b/int-literals.go",
+ "@@ -1,3 +1,9 @@",
+ " const (",
+ "+a = 4, b = 5, c = 6",
+ "+)",
+ "+const (",
+ "+a = 1, b = 2, c = 3",
+ "+)",
+ "+const (",
+ " a = 1, b = 2, c = 3",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "dcbb201fb43382e157a6cd1390792a645cff048d"
+ "shas": "5a8ab389323c7a93aca3b7eef89d2b2d2d6f6ff9..e39f6678939d5cfd743fa9d3dfa141c2c9442d15"
}
,{
"testCaseDescription": "go-int-literals-delete-insert-test",
@@ -130,81 +343,84 @@
"replace": [
{
"start": [
- 4,
- 12
+ 2,
+ 5
],
"end": [
- 4,
- 13
+ 2,
+ 6
]
},
{
"start": [
- 4,
- 12
+ 2,
+ 5
],
"end": [
- 4,
- 13
+ 2,
+ 6
]
}
]
},
- "summary": "Replaced '5' with '2' in the identifier variable of the 'main' module"
+ "summary": "Replaced '4' with '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Added '2'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted '5'"
},
{
"span": {
"replace": [
{
"start": [
- 4,
- 5
- ],
- "end": [
- 4,
- 6
- ]
- },
- {
- "start": [
- 4,
- 5
- ],
- "end": [
- 4,
- 6
- ]
- }
- ]
- },
- "summary": "Replaced '4' with '1' in the number variable of the 'main' module"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
+ 2,
19
],
"end": [
- 4,
+ 2,
20
]
},
{
"start": [
- 4,
+ 2,
19
],
"end": [
- 4,
+ 2,
20
]
}
]
},
- "summary": "Replaced '6' with '3' in the number variable of the 'main' module"
+ "summary": "Replaced '6' with '3'"
}
]
},
@@ -213,9 +429,21 @@
"filePaths": [
"int-literals.go"
],
- "sha1": "dcbb201fb43382e157a6cd1390792a645cff048d",
+ "patch": [
+ "diff --git a/int-literals.go b/int-literals.go",
+ "index c8fc4e8..5e0181f 100644",
+ "--- a/int-literals.go",
+ "+++ b/int-literals.go",
+ "@@ -1,5 +1,5 @@",
+ " const (",
+ "-a = 4, b = 5, c = 6",
+ "+a = 1, b = 2, c = 3",
+ " )",
+ " const (",
+ " a = 1, b = 2, c = 3"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3a72aeb457802abb37426fecedabaedefec4edaf"
+ "shas": "e39f6678939d5cfd743fa9d3dfa141c2c9442d15..d4ff1dbca9a259b6d34aac6d77681aea2276ce30"
}
,{
"testCaseDescription": "go-int-literals-replacement-test",
@@ -227,81 +455,84 @@
"replace": [
{
"start": [
- 4,
- 12
+ 2,
+ 5
],
"end": [
- 4,
- 13
+ 2,
+ 6
]
},
{
"start": [
- 4,
- 12
+ 2,
+ 5
],
"end": [
- 4,
- 13
+ 2,
+ 6
]
}
]
},
- "summary": "Replaced '2' with '5' in the identifier variable of the 'main' module"
+ "summary": "Replaced '1' with '4'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Added '5'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted '2'"
},
{
"span": {
"replace": [
{
"start": [
- 4,
- 5
- ],
- "end": [
- 4,
- 6
- ]
- },
- {
- "start": [
- 4,
- 5
- ],
- "end": [
- 4,
- 6
- ]
- }
- ]
- },
- "summary": "Replaced '1' with '4' in the number variable of the 'main' module"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
+ 2,
19
],
"end": [
- 4,
+ 2,
20
]
},
{
"start": [
- 4,
+ 2,
19
],
"end": [
- 4,
+ 2,
20
]
}
]
},
- "summary": "Replaced '3' with '6' in the number variable of the 'main' module"
+ "summary": "Replaced '3' with '6'"
}
]
},
@@ -310,9 +541,21 @@
"filePaths": [
"int-literals.go"
],
- "sha1": "3a72aeb457802abb37426fecedabaedefec4edaf",
+ "patch": [
+ "diff --git a/int-literals.go b/int-literals.go",
+ "index 5e0181f..c8fc4e8 100644",
+ "--- a/int-literals.go",
+ "+++ b/int-literals.go",
+ "@@ -1,5 +1,5 @@",
+ " const (",
+ "-a = 1, b = 2, c = 3",
+ "+a = 4, b = 5, c = 6",
+ " )",
+ " const (",
+ " a = 1, b = 2, c = 3"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "de6a6a16a83928a81e5cb1b3ceb1d7abe24368d8"
+ "shas": "d4ff1dbca9a259b6d34aac6d77681aea2276ce30..4839c8fa790d4d8b59cd8c4804b2c570c99a4a4f"
}
,{
"testCaseDescription": "go-int-literals-delete-replacement-test",
@@ -321,93 +564,183 @@
"int-literals.go": [
{
"span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 5,
- 2
- ]
- }
+ "replace": [
+ {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ },
+ {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ ]
},
- "summary": "Deleted the 'identifier' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 5,
- 2
- ]
- }
- },
- "summary": "Deleted the 'number' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 6,
- 1
- ],
- "end": [
- 8,
- 2
- ]
- }
- },
- "summary": "Deleted the 'identifier' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 6,
- 1
- ],
- "end": [
- 8,
- 2
- ]
- }
- },
- "summary": "Deleted the 'number' variable"
+ "summary": "Replaced '4' with '1'"
},
{
"span": {
"insert": {
"start": [
- 6,
- 1
+ 2,
+ 12
],
"end": [
- 8,
- 2
+ 2,
+ 13
]
}
},
- "summary": "Added the 'identifier' variable"
+ "summary": "Added '2'"
},
{
"span": {
- "insert": {
+ "delete": {
"start": [
- 6,
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted '5'"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 2,
+ 19
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ },
+ {
+ "start": [
+ 2,
+ 19
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced '6' with '3'"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 5,
+ 6
+ ]
+ },
+ {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 5,
+ 6
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced '1' with '4'"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 5,
+ 12
+ ],
+ "end": [
+ 5,
+ 13
+ ]
+ },
+ {
+ "start": [
+ 5,
+ 12
+ ],
+ "end": [
+ 5,
+ 13
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced '2' with '5'"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 5,
+ 19
+ ],
+ "end": [
+ 5,
+ 20
+ ]
+ },
+ {
+ "start": [
+ 5,
+ 19
+ ],
+ "end": [
+ 5,
+ 20
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced '3' with '6'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
1
],
"end": [
- 8,
+ 9,
2
]
}
},
- "summary": "Added the 'number' variable"
+ "summary": "Deleted the 'a' variable"
}
]
},
@@ -416,9 +749,25 @@
"filePaths": [
"int-literals.go"
],
- "sha1": "de6a6a16a83928a81e5cb1b3ceb1d7abe24368d8",
+ "patch": [
+ "diff --git a/int-literals.go b/int-literals.go",
+ "index c8fc4e8..44afd3b 100644",
+ "--- a/int-literals.go",
+ "+++ b/int-literals.go",
+ "@@ -1,9 +1,6 @@",
+ " const (",
+ "-a = 4, b = 5, c = 6",
+ "-)",
+ "-const (",
+ " a = 1, b = 2, c = 3",
+ " )",
+ " const (",
+ "-a = 1, b = 2, c = 3",
+ "+a = 4, b = 5, c = 6",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "2f7484fbdf31b527f96f7d42cb7f395854307756"
+ "shas": "4839c8fa790d4d8b59cd8c4804b2c570c99a4a4f..baae9da50006bbd8576a42207f9d6bb13797349d"
}
,{
"testCaseDescription": "go-int-literals-delete-test",
@@ -427,24 +776,93 @@
"int-literals.go": [
{
"span": {
- "delete": {
+ "replace": [
+ {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ },
+ {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced '1' with '4'"
+ },
+ {
+ "span": {
+ "insert": {
"start": [
- 3,
- 1
+ 2,
+ 12
],
"end": [
- 5,
- 2
+ 2,
+ 13
]
}
},
- "summary": "Deleted the 'identifier' variable"
+ "summary": "Added '5'"
},
{
"span": {
"delete": {
"start": [
- 3,
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted '2'"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 2,
+ 19
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ },
+ {
+ "start": [
+ 2,
+ 19
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced '3' with '6'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
1
],
"end": [
@@ -453,7 +871,82 @@
]
}
},
- "summary": "Deleted the 'number' variable"
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 5,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the '4'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 8
+ ],
+ "end": [
+ 5,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 12
+ ],
+ "end": [
+ 5,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted '5'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 15
+ ],
+ "end": [
+ 5,
+ 16
+ ]
+ }
+ },
+ "summary": "Deleted 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 19
+ ],
+ "end": [
+ 5,
+ 20
+ ]
+ }
+ },
+ "summary": "Deleted '6'"
}
]
},
@@ -462,9 +955,21 @@
"filePaths": [
"int-literals.go"
],
- "sha1": "2f7484fbdf31b527f96f7d42cb7f395854307756",
+ "patch": [
+ "diff --git a/int-literals.go b/int-literals.go",
+ "index 44afd3b..0e70b15 100644",
+ "--- a/int-literals.go",
+ "+++ b/int-literals.go",
+ "@@ -1,6 +1,3 @@",
+ " const (",
+ "-a = 1, b = 2, c = 3",
+ "-)",
+ "-const (",
+ " a = 4, b = 5, c = 6",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "318de8d537443eab2f71a9666927b7e7a1b674df"
+ "shas": "baae9da50006bbd8576a42207f9d6bb13797349d..61b08576920bd19b1e47b300f777e1ee3daebd82"
}
,{
"testCaseDescription": "go-int-literals-delete-rest-test",
@@ -475,31 +980,91 @@
"span": {
"delete": {
"start": [
- 3,
+ 2,
1
],
"end": [
- 5,
+ 2,
2
]
}
},
- "summary": "Deleted the 'identifier' variable"
+ "summary": "Deleted 'a' identifier"
},
{
"span": {
"delete": {
"start": [
- 3,
- 1
+ 2,
+ 5
],
"end": [
- 5,
- 2
+ 2,
+ 6
]
}
},
- "summary": "Deleted the 'number' variable"
+ "summary": "Deleted '4'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 8
+ ],
+ "end": [
+ 2,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted '5'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 15
+ ],
+ "end": [
+ 2,
+ 16
+ ]
+ }
+ },
+ "summary": "Deleted 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 19
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ }
+ },
+ "summary": "Deleted '6'"
}
]
},
@@ -508,7 +1073,16 @@
"filePaths": [
"int-literals.go"
],
- "sha1": "318de8d537443eab2f71a9666927b7e7a1b674df",
+ "patch": [
+ "diff --git a/int-literals.go b/int-literals.go",
+ "index 0e70b15..e69de29 100644",
+ "--- a/int-literals.go",
+ "+++ b/int-literals.go",
+ "@@ -1,3 +0,0 @@",
+ "-const (",
+ "-a = 4, b = 5, c = 6",
+ "-)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b320a69e5c137c5545033f688550f587c255cd27"
+ "shas": "61b08576920bd19b1e47b300f777e1ee3daebd82..4c2cd3b8d03249a567a8ce63cdf8b9f5e4fd098c"
}]
diff --git a/test/corpus/diff-summaries/go/interface-types.json b/test/corpus/diff-summaries/go/interface-types.json
index 90462e290..f9706746e 100644
--- a/test/corpus/diff-summaries/go/interface-types.json
+++ b/test/corpus/diff-summaries/go/interface-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
21
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
21
],
"end": [
- 4,
+ 2,
23
]
}
@@ -67,11 +67,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
24
],
"end": [
- 4,
+ 2,
30
]
}
@@ -82,11 +82,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -97,11 +97,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -112,11 +112,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -127,11 +127,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
4
],
"end": [
- 7,
+ 5,
10
]
}
@@ -142,11 +142,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
2
],
"end": [
- 8,
+ 6,
12
]
}
@@ -157,11 +157,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
13
],
"end": [
- 8,
+ 6,
14
]
}
@@ -172,11 +172,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
15
],
"end": [
- 8,
+ 6,
21
]
}
@@ -187,11 +187,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
23
],
"end": [
- 8,
+ 6,
28
]
}
@@ -205,9 +205,22 @@
"filePaths": [
"interface-types.go"
],
- "sha1": "728019c0b896205942333966d15ec7058abf5edd",
+ "patch": [
+ "diff --git a/interface-types.go b/interface-types.go",
+ "index e69de29..7f8493c 100644",
+ "--- a/interface-types.go",
+ "+++ b/interface-types.go",
+ "@@ -0,0 +1,7 @@",
+ "+type i1 interface {}",
+ "+type i2 interface { io.Reader }",
+ "+type i3 interface {",
+ "+i1",
+ "+io.Reader",
+ "+ SomeMethod(s string) error",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "479c023b591447db1971b4f2d1760e3980c81675"
+ "shas": "68a6be5450d3faa920cd8148a582aacf50d05b22..c3a161e4b63779b44e2c92805df414ac93bf1088"
}
,{
"testCaseDescription": "go-interface-types-replacement-insert-test",
@@ -218,11 +231,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -233,11 +246,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
21
]
}
@@ -248,11 +261,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -263,11 +276,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
21
],
"end": [
- 4,
+ 2,
23
]
}
@@ -278,11 +291,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
24
],
"end": [
- 4,
+ 2,
30
]
}
@@ -293,11 +306,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -308,11 +321,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -323,11 +336,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -338,11 +351,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
4
],
"end": [
- 7,
+ 5,
10
]
}
@@ -353,11 +366,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
2
],
"end": [
- 8,
+ 6,
12
]
}
@@ -368,11 +381,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
13
],
"end": [
- 8,
+ 6,
14
]
}
@@ -383,11 +396,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
15
],
"end": [
- 8,
+ 6,
21
]
}
@@ -398,11 +411,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
23
],
"end": [
- 8,
+ 6,
28
]
}
@@ -413,11 +426,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
6
],
"end": [
- 10,
+ 8,
8
]
}
@@ -428,11 +441,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
9
],
"end": [
- 10,
+ 8,
21
]
}
@@ -443,11 +456,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
6
],
"end": [
- 11,
+ 9,
8
]
}
@@ -458,11 +471,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
21
],
"end": [
- 11,
+ 9,
23
]
}
@@ -473,11 +486,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
24
],
"end": [
- 11,
+ 9,
30
]
}
@@ -488,11 +501,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
6
],
"end": [
- 12,
+ 10,
8
]
}
@@ -503,11 +516,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 11,
1
],
"end": [
- 13,
+ 11,
3
]
}
@@ -518,11 +531,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 12,
1
],
"end": [
- 14,
+ 12,
3
]
}
@@ -533,11 +546,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 12,
4
],
"end": [
- 14,
+ 12,
10
]
}
@@ -548,11 +561,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
2
],
"end": [
- 15,
+ 13,
12
]
}
@@ -563,11 +576,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
13
],
"end": [
- 15,
+ 13,
14
]
}
@@ -578,11 +591,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
15
],
"end": [
- 15,
+ 13,
21
]
}
@@ -593,11 +606,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
23
],
"end": [
- 15,
+ 13,
28
]
}
@@ -611,9 +624,32 @@
"filePaths": [
"interface-types.go"
],
- "sha1": "479c023b591447db1971b4f2d1760e3980c81675",
+ "patch": [
+ "diff --git a/interface-types.go b/interface-types.go",
+ "index 7f8493c..8ad5847 100644",
+ "--- a/interface-types.go",
+ "+++ b/interface-types.go",
+ "@@ -1,3 +1,17 @@",
+ "+type j1 interface {}",
+ "+type j2 interface { io.Reader }",
+ "+type j3 interface {",
+ "+i1",
+ "+io.Reader",
+ "+ SomeMethod(s string) error",
+ "+}",
+ "+type i1 interface {}",
+ "+type i2 interface { io.Reader }",
+ "+type i3 interface {",
+ "+i1",
+ "+io.Reader",
+ "+ SomeMethod(s string) error",
+ "+}",
+ " type i1 interface {}",
+ " type i2 interface { io.Reader }",
+ " type i3 interface {"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "614b595fa47140bbdbc220c96c97c8bd7733d81f"
+ "shas": "c3a161e4b63779b44e2c92805df414ac93bf1088..6c6f0a26477322ea443c184c6de4d249682f084f"
}
,{
"testCaseDescription": "go-interface-types-delete-insert-test",
@@ -625,21 +661,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -652,21 +688,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -679,21 +715,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -708,9 +744,24 @@
"filePaths": [
"interface-types.go"
],
- "sha1": "614b595fa47140bbdbc220c96c97c8bd7733d81f",
+ "patch": [
+ "diff --git a/interface-types.go b/interface-types.go",
+ "index 8ad5847..105bfc8 100644",
+ "--- a/interface-types.go",
+ "+++ b/interface-types.go",
+ "@@ -1,6 +1,6 @@",
+ "-type j1 interface {}",
+ "-type j2 interface { io.Reader }",
+ "-type j3 interface {",
+ "+type i1 interface {}",
+ "+type i2 interface { io.Reader }",
+ "+type i3 interface {",
+ " i1",
+ " io.Reader",
+ " SomeMethod(s string) error"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "56a0aef20e33d5a164df7ed7bcc29b4dbb621e4b"
+ "shas": "6c6f0a26477322ea443c184c6de4d249682f084f..70a67d481c42e5ceb5cd815380b35b9da3207adc"
}
,{
"testCaseDescription": "go-interface-types-replacement-test",
@@ -722,21 +773,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -749,21 +800,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -776,21 +827,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -805,9 +856,24 @@
"filePaths": [
"interface-types.go"
],
- "sha1": "56a0aef20e33d5a164df7ed7bcc29b4dbb621e4b",
+ "patch": [
+ "diff --git a/interface-types.go b/interface-types.go",
+ "index 105bfc8..8ad5847 100644",
+ "--- a/interface-types.go",
+ "+++ b/interface-types.go",
+ "@@ -1,6 +1,6 @@",
+ "-type i1 interface {}",
+ "-type i2 interface { io.Reader }",
+ "-type i3 interface {",
+ "+type j1 interface {}",
+ "+type j2 interface { io.Reader }",
+ "+type j3 interface {",
+ " i1",
+ " io.Reader",
+ " SomeMethod(s string) error"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ef3c8f435489c311ff2a8800c1aeb1dd59349741"
+ "shas": "70a67d481c42e5ceb5cd815380b35b9da3207adc..f3630526601f49c4583ac382943596c3972fc14f"
}
,{
"testCaseDescription": "go-interface-types-delete-replacement-test",
@@ -818,11 +884,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -833,11 +899,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
21
]
}
@@ -848,11 +914,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -863,11 +929,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
21
],
"end": [
- 4,
+ 2,
23
]
}
@@ -878,11 +944,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
24
],
"end": [
- 4,
+ 2,
30
]
}
@@ -893,11 +959,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -908,11 +974,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -923,11 +989,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -938,11 +1004,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
4
],
"end": [
- 7,
+ 5,
10
]
}
@@ -953,11 +1019,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
2
],
"end": [
- 8,
+ 6,
12
]
}
@@ -968,11 +1034,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
13
],
"end": [
- 8,
+ 6,
14
]
}
@@ -983,11 +1049,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
15
],
"end": [
- 8,
+ 6,
21
]
}
@@ -998,11 +1064,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
23
],
"end": [
- 8,
+ 6,
28
]
}
@@ -1013,11 +1079,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
6
],
"end": [
- 10,
+ 8,
8
]
}
@@ -1028,11 +1094,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
9
],
"end": [
- 10,
+ 8,
21
]
}
@@ -1043,11 +1109,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
6
],
"end": [
- 11,
+ 9,
8
]
}
@@ -1058,11 +1124,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
21
],
"end": [
- 11,
+ 9,
23
]
}
@@ -1073,11 +1139,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
24
],
"end": [
- 11,
+ 9,
30
]
}
@@ -1088,11 +1154,11 @@
"span": {
"delete": {
"start": [
- 12,
+ 10,
6
],
"end": [
- 12,
+ 10,
8
]
}
@@ -1103,11 +1169,11 @@
"span": {
"delete": {
"start": [
- 13,
+ 11,
1
],
"end": [
- 13,
+ 11,
3
]
}
@@ -1118,11 +1184,11 @@
"span": {
"delete": {
"start": [
- 14,
+ 12,
1
],
"end": [
- 14,
+ 12,
3
]
}
@@ -1133,11 +1199,11 @@
"span": {
"delete": {
"start": [
- 14,
+ 12,
4
],
"end": [
- 14,
+ 12,
10
]
}
@@ -1148,11 +1214,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
2
],
"end": [
- 15,
+ 13,
12
]
}
@@ -1163,11 +1229,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
13
],
"end": [
- 15,
+ 13,
14
]
}
@@ -1178,11 +1244,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
15
],
"end": [
- 15,
+ 13,
21
]
}
@@ -1193,11 +1259,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
23
],
"end": [
- 15,
+ 13,
28
]
}
@@ -1208,11 +1274,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
6
],
"end": [
- 10,
+ 8,
8
]
}
@@ -1223,11 +1289,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
9
],
"end": [
- 10,
+ 8,
21
]
}
@@ -1238,11 +1304,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
6
],
"end": [
- 11,
+ 9,
8
]
}
@@ -1253,11 +1319,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
21
],
"end": [
- 11,
+ 9,
23
]
}
@@ -1268,11 +1334,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
24
],
"end": [
- 11,
+ 9,
30
]
}
@@ -1283,11 +1349,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
6
],
"end": [
- 12,
+ 10,
8
]
}
@@ -1298,11 +1364,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 11,
1
],
"end": [
- 13,
+ 11,
3
]
}
@@ -1313,11 +1379,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 12,
1
],
"end": [
- 14,
+ 12,
3
]
}
@@ -1328,11 +1394,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 12,
4
],
"end": [
- 14,
+ 12,
10
]
}
@@ -1343,11 +1409,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
2
],
"end": [
- 15,
+ 13,
12
]
}
@@ -1358,11 +1424,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
13
],
"end": [
- 15,
+ 13,
14
]
}
@@ -1373,11 +1439,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
15
],
"end": [
- 15,
+ 13,
21
]
}
@@ -1388,11 +1454,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
23
],
"end": [
- 15,
+ 13,
28
]
}
@@ -1406,9 +1472,38 @@
"filePaths": [
"interface-types.go"
],
- "sha1": "ef3c8f435489c311ff2a8800c1aeb1dd59349741",
+ "patch": [
+ "diff --git a/interface-types.go b/interface-types.go",
+ "index 8ad5847..7ff818b 100644",
+ "--- a/interface-types.go",
+ "+++ b/interface-types.go",
+ "@@ -1,10 +1,3 @@",
+ "-type j1 interface {}",
+ "-type j2 interface { io.Reader }",
+ "-type j3 interface {",
+ "-i1",
+ "-io.Reader",
+ "- SomeMethod(s string) error",
+ "-}",
+ " type i1 interface {}",
+ " type i2 interface { io.Reader }",
+ " type i3 interface {",
+ "@@ -12,9 +5,9 @@ i1",
+ " io.Reader",
+ " SomeMethod(s string) error",
+ " }",
+ "-type i1 interface {}",
+ "-type i2 interface { io.Reader }",
+ "-type i3 interface {",
+ "+type j1 interface {}",
+ "+type j2 interface { io.Reader }",
+ "+type j3 interface {",
+ " i1",
+ " io.Reader",
+ " SomeMethod(s string) error"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e00dc2a1614395b65d8e85a536e3c7d7e80a38ba"
+ "shas": "f3630526601f49c4583ac382943596c3972fc14f..3c75edf9d8c8aac6af1024c19a0d72c810cdafe3"
}
,{
"testCaseDescription": "go-interface-types-delete-test",
@@ -1419,11 +1514,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -1434,11 +1529,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
21
]
}
@@ -1449,11 +1544,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -1464,11 +1559,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
21
],
"end": [
- 4,
+ 2,
23
]
}
@@ -1479,11 +1574,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
24
],
"end": [
- 4,
+ 2,
30
]
}
@@ -1494,11 +1589,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -1509,11 +1604,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -1524,11 +1619,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -1539,11 +1634,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
4
],
"end": [
- 7,
+ 5,
10
]
}
@@ -1554,11 +1649,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
2
],
"end": [
- 8,
+ 6,
12
]
}
@@ -1569,11 +1664,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
13
],
"end": [
- 8,
+ 6,
14
]
}
@@ -1584,11 +1679,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
15
],
"end": [
- 8,
+ 6,
21
]
}
@@ -1599,11 +1694,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
23
],
"end": [
- 8,
+ 6,
28
]
}
@@ -1617,9 +1712,25 @@
"filePaths": [
"interface-types.go"
],
- "sha1": "e00dc2a1614395b65d8e85a536e3c7d7e80a38ba",
+ "patch": [
+ "diff --git a/interface-types.go b/interface-types.go",
+ "index 7ff818b..eb92de5 100644",
+ "--- a/interface-types.go",
+ "+++ b/interface-types.go",
+ "@@ -1,10 +1,3 @@",
+ "-type i1 interface {}",
+ "-type i2 interface { io.Reader }",
+ "-type i3 interface {",
+ "-i1",
+ "-io.Reader",
+ "- SomeMethod(s string) error",
+ "-}",
+ " type j1 interface {}",
+ " type j2 interface { io.Reader }",
+ " type j3 interface {"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "9484e06029a987b400e6fef739e2cc417d0b0ac0"
+ "shas": "3c75edf9d8c8aac6af1024c19a0d72c810cdafe3..785723423fc2b7ba95d0b724df63e663178e4333"
}
,{
"testCaseDescription": "go-interface-types-delete-rest-test",
@@ -1630,11 +1741,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -1645,11 +1756,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
21
]
}
@@ -1660,11 +1771,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -1675,11 +1786,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
21
],
"end": [
- 4,
+ 2,
23
]
}
@@ -1690,11 +1801,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
24
],
"end": [
- 4,
+ 2,
30
]
}
@@ -1705,11 +1816,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -1720,11 +1831,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
3
]
}
@@ -1735,11 +1846,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
3
]
}
@@ -1750,11 +1861,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
4
],
"end": [
- 7,
+ 5,
10
]
}
@@ -1765,11 +1876,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
2
],
"end": [
- 8,
+ 6,
12
]
}
@@ -1780,11 +1891,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
13
],
"end": [
- 8,
+ 6,
14
]
}
@@ -1795,11 +1906,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
15
],
"end": [
- 8,
+ 6,
21
]
}
@@ -1810,11 +1921,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
23
],
"end": [
- 8,
+ 6,
28
]
}
@@ -1828,7 +1939,20 @@
"filePaths": [
"interface-types.go"
],
- "sha1": "9484e06029a987b400e6fef739e2cc417d0b0ac0",
+ "patch": [
+ "diff --git a/interface-types.go b/interface-types.go",
+ "index eb92de5..e69de29 100644",
+ "--- a/interface-types.go",
+ "+++ b/interface-types.go",
+ "@@ -1,7 +0,0 @@",
+ "-type j1 interface {}",
+ "-type j2 interface { io.Reader }",
+ "-type j3 interface {",
+ "-i1",
+ "-io.Reader",
+ "- SomeMethod(s string) error",
+ "-}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c818cf5bb28cfc9175040ba099cef324698884d8"
+ "shas": "785723423fc2b7ba95d0b724df63e663178e4333..ce33c1bfeb0cbfdd024d65479c25db256cdd12cc"
}]
diff --git a/test/corpus/diff-summaries/go/label-statements.json b/test/corpus/diff-summaries/go/label-statements.json
index 8f5f8a60c..4cd8485a6 100644
--- a/test/corpus/diff-summaries/go/label-statements.json
+++ b/test/corpus/diff-summaries/go/label-statements.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
15
]
}
@@ -25,9 +25,18 @@
"filePaths": [
"label-statements.go"
],
- "sha1": "c69fcfce40f178714107964705a6370513f7733e",
+ "patch": [
+ "diff --git a/label-statements.go b/label-statements.go",
+ "index e69de29..d0544fe 100644",
+ "--- a/label-statements.go",
+ "+++ b/label-statements.go",
+ "@@ -0,0 +1,3 @@",
+ "+{",
+ "+ insert_label:",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "06dfc9d634af0ab6cd3b7040a3abc3ace1d63978"
+ "shas": "b36463027cca058b97d4495c8c08a1ab9ab5cc0a..1fc84483617cdb29cf050b0bc3d87b01f6a13861"
}
,{
"testCaseDescription": "go-label-statements-replacement-insert-test",
@@ -36,30 +45,33 @@
"label-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 6,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'replacement_label' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 3
+ ],
+ "end": [
+ 5,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'insert_label' identifier"
}
]
},
@@ -68,9 +80,24 @@
"filePaths": [
"label-statements.go"
],
- "sha1": "06dfc9d634af0ab6cd3b7040a3abc3ace1d63978",
+ "patch": [
+ "diff --git a/label-statements.go b/label-statements.go",
+ "index d0544fe..745311d 100644",
+ "--- a/label-statements.go",
+ "+++ b/label-statements.go",
+ "@@ -1,3 +1,9 @@",
+ " {",
+ "+ replacement_label:",
+ "+}",
+ "+{",
+ "+ insert_label:",
+ "+}",
+ "+{",
+ " insert_label:",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "d8bee422a1feb5d4dbe64d7347f3e79ef8aebebf"
+ "shas": "1fc84483617cdb29cf050b0bc3d87b01f6a13861..0ac867b531ff4bcdb53b74c34c691ba7953b5f59"
}
,{
"testCaseDescription": "go-label-statements-delete-insert-test",
@@ -82,21 +109,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
20
]
},
{
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
15
]
}
@@ -111,9 +138,21 @@
"filePaths": [
"label-statements.go"
],
- "sha1": "d8bee422a1feb5d4dbe64d7347f3e79ef8aebebf",
+ "patch": [
+ "diff --git a/label-statements.go b/label-statements.go",
+ "index 745311d..be34b5c 100644",
+ "--- a/label-statements.go",
+ "+++ b/label-statements.go",
+ "@@ -1,5 +1,5 @@",
+ " {",
+ "- replacement_label:",
+ "+ insert_label:",
+ " }",
+ " {",
+ " insert_label:"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3ffc48383ff965acde1cb61bf128dba6b5a956b3"
+ "shas": "0ac867b531ff4bcdb53b74c34c691ba7953b5f59..8816a0dfb9ed2e8ce865f18a22e0a0fea91a972f"
}
,{
"testCaseDescription": "go-label-statements-replacement-test",
@@ -125,21 +164,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
15
]
},
{
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
20
]
}
@@ -154,9 +193,21 @@
"filePaths": [
"label-statements.go"
],
- "sha1": "3ffc48383ff965acde1cb61bf128dba6b5a956b3",
+ "patch": [
+ "diff --git a/label-statements.go b/label-statements.go",
+ "index be34b5c..745311d 100644",
+ "--- a/label-statements.go",
+ "+++ b/label-statements.go",
+ "@@ -1,5 +1,5 @@",
+ " {",
+ "- insert_label:",
+ "+ replacement_label:",
+ " }",
+ " {",
+ " insert_label:"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f0999f5fb8404d7bf45b5b48a29f7594b3b1d59c"
+ "shas": "8816a0dfb9ed2e8ce865f18a22e0a0fea91a972f..86835321d9dfbb9cc746ae02c27c84f687d8588b"
}
,{
"testCaseDescription": "go-label-statements-delete-replacement-test",
@@ -167,11 +218,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
20
]
}
@@ -182,11 +233,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
3
],
"end": [
- 7,
+ 5,
15
]
}
@@ -197,11 +248,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
3
],
"end": [
- 7,
+ 5,
20
]
}
@@ -215,9 +266,25 @@
"filePaths": [
"label-statements.go"
],
- "sha1": "f0999f5fb8404d7bf45b5b48a29f7594b3b1d59c",
+ "patch": [
+ "diff --git a/label-statements.go b/label-statements.go",
+ "index 745311d..57f6c03 100644",
+ "--- a/label-statements.go",
+ "+++ b/label-statements.go",
+ "@@ -1,9 +1,6 @@",
+ " {",
+ "- replacement_label:",
+ "-}",
+ "-{",
+ " insert_label:",
+ " }",
+ " {",
+ "- insert_label:",
+ "+ replacement_label:",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "2d8e39fcd4c65814192407daa7416f6e3c50bb0a"
+ "shas": "86835321d9dfbb9cc746ae02c27c84f687d8588b..a86d97f2c6fe8abfe2a8f90c19b251059943d7a7"
}
,{
"testCaseDescription": "go-label-statements-delete-test",
@@ -226,30 +293,18 @@
"label-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 6,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 15
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'insert_label' identifier"
}
]
},
@@ -258,9 +313,21 @@
"filePaths": [
"label-statements.go"
],
- "sha1": "2d8e39fcd4c65814192407daa7416f6e3c50bb0a",
+ "patch": [
+ "diff --git a/label-statements.go b/label-statements.go",
+ "index 57f6c03..6920e65 100644",
+ "--- a/label-statements.go",
+ "+++ b/label-statements.go",
+ "@@ -1,6 +1,3 @@",
+ " {",
+ "- insert_label:",
+ "-}",
+ "-{",
+ " replacement_label:",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "194bc6d2f7a068a5fcb156d56ed4ad56dcbdf0c2"
+ "shas": "a86d97f2c6fe8abfe2a8f90c19b251059943d7a7..71d4de7371642308a8d1786d6cb88461d4aaf8b5"
}
,{
"testCaseDescription": "go-label-statements-delete-rest-test",
@@ -271,11 +338,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
20
]
}
@@ -289,7 +356,16 @@
"filePaths": [
"label-statements.go"
],
- "sha1": "194bc6d2f7a068a5fcb156d56ed4ad56dcbdf0c2",
+ "patch": [
+ "diff --git a/label-statements.go b/label-statements.go",
+ "index 6920e65..e69de29 100644",
+ "--- a/label-statements.go",
+ "+++ b/label-statements.go",
+ "@@ -1,3 +0,0 @@",
+ "-{",
+ "- replacement_label:",
+ "-}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "150f53c8cfb31186993a9588c913d8bcad3cef1d"
+ "shas": "71d4de7371642308a8d1786d6cb88461d4aaf8b5..ca9ffb9a8bca75e34a2383f7d503d3b21d7b08cc"
}]
diff --git a/test/corpus/diff-summaries/go/map-literals.json b/test/corpus/diff-summaries/go/map-literals.json
index 0765f9a1d..49a52045b 100644
--- a/test/corpus/diff-summaries/go/map-literals.json
+++ b/test/corpus/diff-summaries/go/map-literals.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -25,9 +25,19 @@
"filePaths": [
"map-literals.go"
],
- "sha1": "3003ac02afb103f388ce64e485de8c028c6eb629",
+ "patch": [
+ "diff --git a/map-literals.go b/map-literals.go",
+ "index e69de29..16fb3cf 100644",
+ "--- a/map-literals.go",
+ "+++ b/map-literals.go",
+ "@@ -0,0 +1,4 @@",
+ "+const s = map[string]string{",
+ "+\"hi\": \"hello\",",
+ "+\"bye\": \"goodbye\",",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "94454acb7983200ae26fddbf57a5a997084c5785"
+ "shas": "02421320cce3bcbcdb5d7bd248eb1aa0ef8aff93..bcf7280bfaabf2abafe3fef0e53c921a6185013d"
}
,{
"testCaseDescription": "go-map-literals-replacement-insert-test",
@@ -38,11 +48,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -53,11 +63,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -71,9 +81,26 @@
"filePaths": [
"map-literals.go"
],
- "sha1": "94454acb7983200ae26fddbf57a5a997084c5785",
+ "patch": [
+ "diff --git a/map-literals.go b/map-literals.go",
+ "index 16fb3cf..b3c30ca 100644",
+ "--- a/map-literals.go",
+ "+++ b/map-literals.go",
+ "@@ -1,3 +1,11 @@",
+ "+const s = map[string]int{",
+ "+\"foo\": \"bar\",",
+ "+\"baz\": \"hello\",",
+ "+}",
+ "+const s = map[string]string{",
+ "+\"hi\": \"hello\",",
+ "+\"bye\": \"goodbye\",",
+ "+}",
+ " const s = map[string]string{",
+ " \"hi\": \"hello\",",
+ " \"bye\": \"goodbye\","
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e895540c5ad838695b46f21a15e66bb47d9d6a19"
+ "shas": "bcf7280bfaabf2abafe3fef0e53c921a6185013d..ac890581fd47d5ebf0c88cac9f5f263442e8c179"
}
,{
"testCaseDescription": "go-map-literals-delete-insert-test",
@@ -85,135 +112,135 @@
"replace": [
{
"start": [
- 3,
+ 1,
22
],
"end": [
- 3,
+ 1,
25
]
},
{
"start": [
- 3,
+ 1,
15
],
"end": [
- 3,
+ 1,
21
]
}
]
},
- "summary": "Replaced the 'int' identifier with the 'string' identifier in the s variable of the 'main' module"
+ "summary": "Replaced the 'int' identifier with the 'string' identifier in the s variable"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
6
]
},
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
5
]
}
]
},
- "summary": "Replaced the \"foo\" string with the \"hi\" string in the s variable of the 'main' module"
+ "summary": "Replaced the \"foo\" string with the \"hi\" string in the s variable"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
13
]
},
{
"start": [
- 4,
+ 2,
7
],
"end": [
- 4,
+ 2,
14
]
}
]
},
- "summary": "Replaced the \"bar\" string with the \"hello\" string in the s variable of the 'main' module"
+ "summary": "Replaced the \"bar\" string with the \"hello\" string in the s variable"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
6
]
},
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
6
]
}
]
},
- "summary": "Replaced the \"baz\" string with the \"bye\" string in the s variable of the 'main' module"
+ "summary": "Replaced the \"baz\" string with the \"bye\" string in the s variable"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
15
]
},
{
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
17
]
}
]
},
- "summary": "Replaced the \"hello\" string with the \"goodbye\" string in the s variable of the 'main' module"
+ "summary": "Replaced the \"hello\" string with the \"goodbye\" string in the s variable"
}
]
},
@@ -222,9 +249,24 @@
"filePaths": [
"map-literals.go"
],
- "sha1": "e895540c5ad838695b46f21a15e66bb47d9d6a19",
+ "patch": [
+ "diff --git a/map-literals.go b/map-literals.go",
+ "index b3c30ca..72c2e91 100644",
+ "--- a/map-literals.go",
+ "+++ b/map-literals.go",
+ "@@ -1,6 +1,6 @@",
+ "-const s = map[string]int{",
+ "-\"foo\": \"bar\",",
+ "-\"baz\": \"hello\",",
+ "+const s = map[string]string{",
+ "+\"hi\": \"hello\",",
+ "+\"bye\": \"goodbye\",",
+ " }",
+ " const s = map[string]string{",
+ " \"hi\": \"hello\","
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "aae53526a90645a92b2df9bea4766951db051b19"
+ "shas": "ac890581fd47d5ebf0c88cac9f5f263442e8c179..dd3d3d371b2bbaf02d99ee3638a84cdfa528793f"
}
,{
"testCaseDescription": "go-map-literals-replacement-test",
@@ -235,118 +277,118 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
15
],
"end": [
- 3,
+ 1,
21
]
}
},
- "summary": "Deleted the 'string' identifier in the s variable of the 'main' module"
+ "summary": "Deleted the 'string' identifier in the s variable"
},
{
"span": {
"insert": {
"start": [
- 3,
+ 1,
22
],
"end": [
- 3,
+ 1,
25
]
}
},
- "summary": "Added the 'int' identifier in the s variable of the 'main' module"
+ "summary": "Added the 'int' identifier in the s variable"
},
{
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
6
]
}
},
- "summary": "Added the \"foo\" string in the s variable of the 'main' module"
+ "summary": "Added the \"foo\" string in the s variable"
},
{
"span": {
"insert": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
13
]
}
},
- "summary": "Added the \"bar\" string in the s variable of the 'main' module"
+ "summary": "Added the \"bar\" string in the s variable"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
5
]
},
{
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
6
]
}
]
},
- "summary": "Replaced the \"hi\" string with the \"baz\" string in the s variable of the 'main' module"
+ "summary": "Replaced the \"hi\" string with the \"baz\" string in the s variable"
},
{
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
6
]
}
},
- "summary": "Deleted the \"bye\" string in the s variable of the 'main' module"
+ "summary": "Deleted the \"bye\" string in the s variable"
},
{
"span": {
"delete": {
"start": [
- 5,
+ 3,
8
],
"end": [
- 5,
+ 3,
17
]
}
},
- "summary": "Deleted the \"goodbye\" string in the s variable of the 'main' module"
+ "summary": "Deleted the \"goodbye\" string in the s variable"
}
]
},
@@ -355,9 +397,24 @@
"filePaths": [
"map-literals.go"
],
- "sha1": "aae53526a90645a92b2df9bea4766951db051b19",
+ "patch": [
+ "diff --git a/map-literals.go b/map-literals.go",
+ "index 72c2e91..b3c30ca 100644",
+ "--- a/map-literals.go",
+ "+++ b/map-literals.go",
+ "@@ -1,6 +1,6 @@",
+ "-const s = map[string]string{",
+ "-\"hi\": \"hello\",",
+ "-\"bye\": \"goodbye\",",
+ "+const s = map[string]int{",
+ "+\"foo\": \"bar\",",
+ "+\"baz\": \"hello\",",
+ " }",
+ " const s = map[string]string{",
+ " \"hi\": \"hello\","
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "da53a715f7eac507f007903e29b8e7ab67ede56b"
+ "shas": "dd3d3d371b2bbaf02d99ee3638a84cdfa528793f..9d7589adf5a08f83cdb1b116e1418f432289e231"
}
,{
"testCaseDescription": "go-map-literals-delete-replacement-test",
@@ -368,11 +425,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -383,11 +440,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -398,11 +455,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -416,9 +473,30 @@
"filePaths": [
"map-literals.go"
],
- "sha1": "da53a715f7eac507f007903e29b8e7ab67ede56b",
+ "patch": [
+ "diff --git a/map-literals.go b/map-literals.go",
+ "index b3c30ca..6d5f577 100644",
+ "--- a/map-literals.go",
+ "+++ b/map-literals.go",
+ "@@ -1,12 +1,8 @@",
+ "-const s = map[string]int{",
+ "-\"foo\": \"bar\",",
+ "-\"baz\": \"hello\",",
+ "-}",
+ " const s = map[string]string{",
+ " \"hi\": \"hello\",",
+ " \"bye\": \"goodbye\",",
+ " }",
+ "-const s = map[string]string{",
+ "-\"hi\": \"hello\",",
+ "-\"bye\": \"goodbye\",",
+ "+const s = map[string]int{",
+ "+\"foo\": \"bar\",",
+ "+\"baz\": \"hello\",",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b4ae265f96300c420b31f7913fe49bbe8e1a57cd"
+ "shas": "9d7589adf5a08f83cdb1b116e1418f432289e231..76fcbf24ccc8c6686db62eff0546be6d97e36608"
}
,{
"testCaseDescription": "go-map-literals-delete-test",
@@ -429,11 +507,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -447,9 +525,22 @@
"filePaths": [
"map-literals.go"
],
- "sha1": "b4ae265f96300c420b31f7913fe49bbe8e1a57cd",
+ "patch": [
+ "diff --git a/map-literals.go b/map-literals.go",
+ "index 6d5f577..7f8e649 100644",
+ "--- a/map-literals.go",
+ "+++ b/map-literals.go",
+ "@@ -1,7 +1,3 @@",
+ "-const s = map[string]string{",
+ "-\"hi\": \"hello\",",
+ "-\"bye\": \"goodbye\",",
+ "-}",
+ " const s = map[string]int{",
+ " \"foo\": \"bar\",",
+ " \"baz\": \"hello\","
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c2adae1038553e500d686b3c2c588562f0747fd7"
+ "shas": "76fcbf24ccc8c6686db62eff0546be6d97e36608..a172d249198eca8d1a97853529cc96e79e8b962a"
}
,{
"testCaseDescription": "go-map-literals-delete-rest-test",
@@ -460,11 +551,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -478,7 +569,17 @@
"filePaths": [
"map-literals.go"
],
- "sha1": "c2adae1038553e500d686b3c2c588562f0747fd7",
+ "patch": [
+ "diff --git a/map-literals.go b/map-literals.go",
+ "index 7f8e649..e69de29 100644",
+ "--- a/map-literals.go",
+ "+++ b/map-literals.go",
+ "@@ -1,4 +0,0 @@",
+ "-const s = map[string]int{",
+ "-\"foo\": \"bar\",",
+ "-\"baz\": \"hello\",",
+ "-}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "bb9bc3e6100eaaf7ccd25a9360f08698cff15981"
+ "shas": "a172d249198eca8d1a97853529cc96e79e8b962a..cd582e9b85e985f87af52085296e006987e8b0d3"
}]
diff --git a/test/corpus/diff-summaries/go/map-types.json b/test/corpus/diff-summaries/go/map-types.json
index c341791a5..85eb69615 100644
--- a/test/corpus/diff-summaries/go/map-types.json
+++ b/test/corpus/diff-summaries/go/map-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
19
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
20
],
"end": [
- 3,
+ 1,
25
]
}
@@ -55,9 +55,16 @@
"filePaths": [
"map-types.go"
],
- "sha1": "c818cf5bb28cfc9175040ba099cef324698884d8",
+ "patch": [
+ "diff --git a/map-types.go b/map-types.go",
+ "index e69de29..c86220d 100644",
+ "--- a/map-types.go",
+ "+++ b/map-types.go",
+ "@@ -0,0 +1 @@",
+ "+type m1 map[string]error"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "2257e7dbe31053042cec06248d42a1043db10de2"
+ "shas": "ce33c1bfeb0cbfdd024d65479c25db256cdd12cc..a17295fbbf8618c6b504245e2b94381ba745ef76"
}
,{
"testCaseDescription": "go-map-types-replacement-insert-test",
@@ -68,11 +75,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -83,11 +90,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
16
]
}
@@ -98,11 +105,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
17
],
"end": [
- 3,
+ 1,
22
]
}
@@ -113,11 +120,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -128,11 +135,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
13
],
"end": [
- 4,
+ 2,
19
]
}
@@ -143,11 +150,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
20
],
"end": [
- 4,
+ 2,
25
]
}
@@ -161,9 +168,18 @@
"filePaths": [
"map-types.go"
],
- "sha1": "2257e7dbe31053042cec06248d42a1043db10de2",
+ "patch": [
+ "diff --git a/map-types.go b/map-types.go",
+ "index c86220d..9cc2e8b 100644",
+ "--- a/map-types.go",
+ "+++ b/map-types.go",
+ "@@ -1 +1,3 @@",
+ "+type m1 map[int]error",
+ "+type m1 map[string]error",
+ " type m1 map[string]error"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "39b66e714f2dd4d4adca6f13fc122f514509e56d"
+ "shas": "a17295fbbf8618c6b504245e2b94381ba745ef76..e911ec9c095a334531d6f7a12da732a3ab64cd9b"
}
,{
"testCaseDescription": "go-map-types-delete-insert-test",
@@ -175,21 +191,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
16
]
},
{
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
19
]
}
@@ -204,9 +220,19 @@
"filePaths": [
"map-types.go"
],
- "sha1": "39b66e714f2dd4d4adca6f13fc122f514509e56d",
+ "patch": [
+ "diff --git a/map-types.go b/map-types.go",
+ "index 9cc2e8b..ee1d5a0 100644",
+ "--- a/map-types.go",
+ "+++ b/map-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-type m1 map[int]error",
+ "+type m1 map[string]error",
+ " type m1 map[string]error",
+ " type m1 map[string]error"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "cce534462eee7e892f598bbb11eae8ddadb8621e"
+ "shas": "e911ec9c095a334531d6f7a12da732a3ab64cd9b..f78f0d563d0a83f7d64cf5b28c854727be528d05"
}
,{
"testCaseDescription": "go-map-types-replacement-test",
@@ -218,21 +244,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
19
]
},
{
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
16
]
}
@@ -247,9 +273,19 @@
"filePaths": [
"map-types.go"
],
- "sha1": "cce534462eee7e892f598bbb11eae8ddadb8621e",
+ "patch": [
+ "diff --git a/map-types.go b/map-types.go",
+ "index ee1d5a0..9cc2e8b 100644",
+ "--- a/map-types.go",
+ "+++ b/map-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-type m1 map[string]error",
+ "+type m1 map[int]error",
+ " type m1 map[string]error",
+ " type m1 map[string]error"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "916b37b7fbb2e41bd54ebb1507daeddef36ebd7b"
+ "shas": "f78f0d563d0a83f7d64cf5b28c854727be528d05..f0967ba8a8380ad4160e1d9c45c1a967f4912ce4"
}
,{
"testCaseDescription": "go-map-types-delete-replacement-test",
@@ -260,11 +296,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -275,11 +311,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
16
]
}
@@ -290,11 +326,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
17
],
"end": [
- 3,
+ 1,
22
]
}
@@ -305,11 +341,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -320,11 +356,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
13
],
"end": [
- 4,
+ 2,
19
]
}
@@ -335,11 +371,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
20
],
"end": [
- 4,
+ 2,
25
]
}
@@ -350,11 +386,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -365,11 +401,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
13
],
"end": [
- 4,
+ 2,
16
]
}
@@ -380,11 +416,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
17
],
"end": [
- 4,
+ 2,
22
]
}
@@ -398,9 +434,19 @@
"filePaths": [
"map-types.go"
],
- "sha1": "916b37b7fbb2e41bd54ebb1507daeddef36ebd7b",
+ "patch": [
+ "diff --git a/map-types.go b/map-types.go",
+ "index 9cc2e8b..a863ca9 100644",
+ "--- a/map-types.go",
+ "+++ b/map-types.go",
+ "@@ -1,3 +1,2 @@",
+ "-type m1 map[int]error",
+ "-type m1 map[string]error",
+ " type m1 map[string]error",
+ "+type m1 map[int]error"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f4ba0647de9d38eba60c257751ae648536d10e6d"
+ "shas": "f0967ba8a8380ad4160e1d9c45c1a967f4912ce4..d48a47fe4d8dd097f68ae843d389105250536d40"
}
,{
"testCaseDescription": "go-map-types-delete-test",
@@ -411,11 +457,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -426,11 +472,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
19
]
}
@@ -441,11 +487,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
20
],
"end": [
- 3,
+ 1,
25
]
}
@@ -459,9 +505,17 @@
"filePaths": [
"map-types.go"
],
- "sha1": "f4ba0647de9d38eba60c257751ae648536d10e6d",
+ "patch": [
+ "diff --git a/map-types.go b/map-types.go",
+ "index a863ca9..d7e6949 100644",
+ "--- a/map-types.go",
+ "+++ b/map-types.go",
+ "@@ -1,2 +1 @@",
+ "-type m1 map[string]error",
+ " type m1 map[int]error"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e8f2c34064e5df9bad4f99414bd81001fea14ab7"
+ "shas": "d48a47fe4d8dd097f68ae843d389105250536d40..56a30334ee9cb89bdae517650927f99c594ec54d"
}
,{
"testCaseDescription": "go-map-types-delete-rest-test",
@@ -472,11 +526,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -487,11 +541,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
13
],
"end": [
- 3,
+ 1,
16
]
}
@@ -502,11 +556,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
17
],
"end": [
- 3,
+ 1,
22
]
}
@@ -520,7 +574,14 @@
"filePaths": [
"map-types.go"
],
- "sha1": "e8f2c34064e5df9bad4f99414bd81001fea14ab7",
+ "patch": [
+ "diff --git a/map-types.go b/map-types.go",
+ "index d7e6949..e69de29 100644",
+ "--- a/map-types.go",
+ "+++ b/map-types.go",
+ "@@ -1 +0,0 @@",
+ "-type m1 map[int]error"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e8c412e8ad778a23678aa9734a72ddbb4d0a3f3e"
+ "shas": "56a30334ee9cb89bdae517650927f99c594ec54d..25efc557c3b81f94924fc76ce4196db1fd75e9cc"
}]
diff --git a/test/corpus/diff-summaries/go/method-declarations.json b/test/corpus/diff-summaries/go/method-declarations.json
index 17684e880..7233cdf39 100644
--- a/test/corpus/diff-summaries/go/method-declarations.json
+++ b/test/corpus/diff-summaries/go/method-declarations.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
11
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
18
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
20
],
"end": [
- 3,
+ 1,
26
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
27
],
"end": [
- 3,
+ 1,
32
]
}
@@ -67,11 +67,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
33
],
"end": [
- 3,
+ 1,
39
]
}
@@ -82,11 +82,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
41
],
"end": [
- 3,
+ 1,
45
]
}
@@ -97,11 +97,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
46
],
"end": [
- 3,
+ 1,
48
]
}
@@ -115,9 +115,16 @@
"filePaths": [
"method-declarations.go"
],
- "sha1": "cbfe90e40b3f1a5f8f1a76f1e2b9dbebe28783ee",
+ "patch": [
+ "diff --git a/method-declarations.go b/method-declarations.go",
+ "index e69de29..4431052 100644",
+ "--- a/method-declarations.go",
+ "+++ b/method-declarations.go",
+ "@@ -0,0 +1 @@",
+ "+func (self Person) Equals(other Person) bool {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "14de9ec3de65ef9f8bc0e5fb6630ff5ac21eaab4"
+ "shas": "d533fb4333ed523cd36d6f2bb4f1c31eb61596f1..1c7c6082448deb0a1a306695dfbb6f9e01160484"
}
,{
"testCaseDescription": "go-method-declarations-replacement-insert-test",
@@ -128,11 +135,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
11
]
}
@@ -143,11 +150,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
15
]
}
@@ -158,11 +165,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
17
],
"end": [
- 3,
+ 1,
23
]
}
@@ -173,11 +180,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
24
],
"end": [
- 3,
+ 1,
29
]
}
@@ -188,11 +195,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
30
],
"end": [
- 3,
+ 1,
33
]
}
@@ -203,11 +210,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
35
],
"end": [
- 3,
+ 1,
39
]
}
@@ -218,11 +225,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
40
],
"end": [
- 3,
+ 1,
42
]
}
@@ -233,11 +240,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
7
],
"end": [
- 4,
+ 2,
11
]
}
@@ -248,11 +255,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
18
]
}
@@ -263,11 +270,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
20
],
"end": [
- 4,
+ 2,
26
]
}
@@ -278,11 +285,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
27
],
"end": [
- 4,
+ 2,
32
]
}
@@ -293,11 +300,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
33
],
"end": [
- 4,
+ 2,
39
]
}
@@ -308,11 +315,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
41
],
"end": [
- 4,
+ 2,
45
]
}
@@ -323,11 +330,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
46
],
"end": [
- 4,
+ 2,
48
]
}
@@ -341,9 +348,18 @@
"filePaths": [
"method-declarations.go"
],
- "sha1": "14de9ec3de65ef9f8bc0e5fb6630ff5ac21eaab4",
+ "patch": [
+ "diff --git a/method-declarations.go b/method-declarations.go",
+ "index 4431052..adbefab 100644",
+ "--- a/method-declarations.go",
+ "+++ b/method-declarations.go",
+ "@@ -1 +1,3 @@",
+ "+func (self Num) Equals(other Num) bool {}",
+ "+func (self Person) Equals(other Person) bool {}",
+ " func (self Person) Equals(other Person) bool {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "5054e15fa1244744a8a8c7d13ab985ef52ec27d7"
+ "shas": "1c7c6082448deb0a1a306695dfbb6f9e01160484..de2a0006cae2a14a2d8d12b21c6ce59f29507870"
}
,{
"testCaseDescription": "go-method-declarations-delete-insert-test",
@@ -355,21 +371,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
15
]
},
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
18
]
}
@@ -382,21 +398,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
30
],
"end": [
- 3,
+ 1,
33
]
},
{
"start": [
- 3,
+ 1,
33
],
"end": [
- 3,
+ 1,
39
]
}
@@ -411,9 +427,19 @@
"filePaths": [
"method-declarations.go"
],
- "sha1": "5054e15fa1244744a8a8c7d13ab985ef52ec27d7",
+ "patch": [
+ "diff --git a/method-declarations.go b/method-declarations.go",
+ "index adbefab..88c36a5 100644",
+ "--- a/method-declarations.go",
+ "+++ b/method-declarations.go",
+ "@@ -1,3 +1,3 @@",
+ "-func (self Num) Equals(other Num) bool {}",
+ "+func (self Person) Equals(other Person) bool {}",
+ " func (self Person) Equals(other Person) bool {}",
+ " func (self Person) Equals(other Person) bool {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e87f60598a56c038968a79ac963c75c931619bce"
+ "shas": "de2a0006cae2a14a2d8d12b21c6ce59f29507870..50c341ba4551b92559db55663bbd8344705582b4"
}
,{
"testCaseDescription": "go-method-declarations-replacement-test",
@@ -425,21 +451,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
18
]
},
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
15
]
}
@@ -452,21 +478,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
33
],
"end": [
- 3,
+ 1,
39
]
},
{
"start": [
- 3,
+ 1,
30
],
"end": [
- 3,
+ 1,
33
]
}
@@ -481,9 +507,19 @@
"filePaths": [
"method-declarations.go"
],
- "sha1": "e87f60598a56c038968a79ac963c75c931619bce",
+ "patch": [
+ "diff --git a/method-declarations.go b/method-declarations.go",
+ "index 88c36a5..adbefab 100644",
+ "--- a/method-declarations.go",
+ "+++ b/method-declarations.go",
+ "@@ -1,3 +1,3 @@",
+ "-func (self Person) Equals(other Person) bool {}",
+ "+func (self Num) Equals(other Num) bool {}",
+ " func (self Person) Equals(other Person) bool {}",
+ " func (self Person) Equals(other Person) bool {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "6068bf44242bbbf53c3e25bbe807eb07c69c4e19"
+ "shas": "50c341ba4551b92559db55663bbd8344705582b4..9a1e61ef7bc553d3764a6d5b88a271466c4dc547"
}
,{
"testCaseDescription": "go-method-declarations-delete-replacement-test",
@@ -494,11 +530,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
11
]
}
@@ -509,11 +545,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
15
]
}
@@ -524,11 +560,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
17
],
"end": [
- 3,
+ 1,
23
]
}
@@ -539,11 +575,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
24
],
"end": [
- 3,
+ 1,
29
]
}
@@ -554,11 +590,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
30
],
"end": [
- 3,
+ 1,
33
]
}
@@ -569,11 +605,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
35
],
"end": [
- 3,
+ 1,
39
]
}
@@ -584,11 +620,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
40
],
"end": [
- 3,
+ 1,
42
]
}
@@ -599,11 +635,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
7
],
"end": [
- 4,
+ 2,
11
]
}
@@ -614,11 +650,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
18
]
}
@@ -629,11 +665,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
20
],
"end": [
- 4,
+ 2,
26
]
}
@@ -644,11 +680,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
27
],
"end": [
- 4,
+ 2,
32
]
}
@@ -659,11 +695,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
33
],
"end": [
- 4,
+ 2,
39
]
}
@@ -674,11 +710,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
41
],
"end": [
- 4,
+ 2,
45
]
}
@@ -689,11 +725,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
46
],
"end": [
- 4,
+ 2,
48
]
}
@@ -704,11 +740,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
7
],
"end": [
- 4,
+ 2,
11
]
}
@@ -719,11 +755,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
15
]
}
@@ -734,11 +770,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
17
],
"end": [
- 4,
+ 2,
23
]
}
@@ -749,11 +785,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
24
],
"end": [
- 4,
+ 2,
29
]
}
@@ -764,11 +800,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
30
],
"end": [
- 4,
+ 2,
33
]
}
@@ -779,11 +815,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
35
],
"end": [
- 4,
+ 2,
39
]
}
@@ -794,11 +830,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
40
],
"end": [
- 4,
+ 2,
42
]
}
@@ -812,9 +848,19 @@
"filePaths": [
"method-declarations.go"
],
- "sha1": "6068bf44242bbbf53c3e25bbe807eb07c69c4e19",
+ "patch": [
+ "diff --git a/method-declarations.go b/method-declarations.go",
+ "index adbefab..9168669 100644",
+ "--- a/method-declarations.go",
+ "+++ b/method-declarations.go",
+ "@@ -1,3 +1,2 @@",
+ "-func (self Num) Equals(other Num) bool {}",
+ "-func (self Person) Equals(other Person) bool {}",
+ " func (self Person) Equals(other Person) bool {}",
+ "+func (self Num) Equals(other Num) bool {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "57eb6787a6123a5d6fee4468ad409e164de5997c"
+ "shas": "9a1e61ef7bc553d3764a6d5b88a271466c4dc547..0004725872e875c81dc295a1e0c89ecf8b4da92d"
}
,{
"testCaseDescription": "go-method-declarations-delete-test",
@@ -825,11 +871,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
11
]
}
@@ -840,11 +886,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
18
]
}
@@ -855,11 +901,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
20
],
"end": [
- 3,
+ 1,
26
]
}
@@ -870,11 +916,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
27
],
"end": [
- 3,
+ 1,
32
]
}
@@ -885,11 +931,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
33
],
"end": [
- 3,
+ 1,
39
]
}
@@ -900,11 +946,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
41
],
"end": [
- 3,
+ 1,
45
]
}
@@ -915,11 +961,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
46
],
"end": [
- 3,
+ 1,
48
]
}
@@ -933,9 +979,17 @@
"filePaths": [
"method-declarations.go"
],
- "sha1": "57eb6787a6123a5d6fee4468ad409e164de5997c",
+ "patch": [
+ "diff --git a/method-declarations.go b/method-declarations.go",
+ "index 9168669..64a70fa 100644",
+ "--- a/method-declarations.go",
+ "+++ b/method-declarations.go",
+ "@@ -1,2 +1 @@",
+ "-func (self Person) Equals(other Person) bool {}",
+ " func (self Num) Equals(other Num) bool {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "01f7c70d4627963d529697f038404d69754c7b60"
+ "shas": "0004725872e875c81dc295a1e0c89ecf8b4da92d..fb4aef49e696686ec2a1195a49571eb3f53ace5e"
}
,{
"testCaseDescription": "go-method-declarations-delete-rest-test",
@@ -946,11 +1000,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
11
]
}
@@ -961,11 +1015,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
15
]
}
@@ -976,11 +1030,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
17
],
"end": [
- 3,
+ 1,
23
]
}
@@ -991,11 +1045,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
24
],
"end": [
- 3,
+ 1,
29
]
}
@@ -1006,11 +1060,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
30
],
"end": [
- 3,
+ 1,
33
]
}
@@ -1021,11 +1075,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
35
],
"end": [
- 3,
+ 1,
39
]
}
@@ -1036,11 +1090,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
40
],
"end": [
- 3,
+ 1,
42
]
}
@@ -1054,7 +1108,14 @@
"filePaths": [
"method-declarations.go"
],
- "sha1": "01f7c70d4627963d529697f038404d69754c7b60",
+ "patch": [
+ "diff --git a/method-declarations.go b/method-declarations.go",
+ "index 64a70fa..e69de29 100644",
+ "--- a/method-declarations.go",
+ "+++ b/method-declarations.go",
+ "@@ -1 +0,0 @@",
+ "-func (self Num) Equals(other Num) bool {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "262ad8491999ea66eb0f840c0b00851ebce2af55"
+ "shas": "fb4aef49e696686ec2a1195a49571eb3f53ace5e..d09227c96ba4107fb4b848d1ef05e13e92fa41a7"
}]
diff --git a/test/corpus/diff-summaries/go/pointer-types.json b/test/corpus/diff-summaries/go/pointer-types.json
index 29aaf7daf..33af25fcf 100644
--- a/test/corpus/diff-summaries/go/pointer-types.json
+++ b/test/corpus/diff-summaries/go/pointer-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
11
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -70,9 +70,19 @@
"filePaths": [
"pointer-types.go"
],
- "sha1": "e8c412e8ad778a23678aa9734a72ddbb4d0a3f3e",
+ "patch": [
+ "diff --git a/pointer-types.go b/pointer-types.go",
+ "index e69de29..05b4659 100644",
+ "--- a/pointer-types.go",
+ "+++ b/pointer-types.go",
+ "@@ -0,0 +1,4 @@",
+ "+type (",
+ "+p1 *string",
+ "+p2 **p1",
+ "+)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "2609295792db8611d8b08bbee5435b5864a2f212"
+ "shas": "25efc557c3b81f94924fc76ce4196db1fd75e9cc..7d8cd7f79e26327a145c2e37f193db0f0aa1b49b"
}
,{
"testCaseDescription": "go-pointer-types-replacement-insert-test",
@@ -83,11 +93,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -98,11 +108,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
}
@@ -113,11 +123,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -128,11 +138,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -143,11 +153,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
3
]
}
@@ -158,11 +168,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
5
],
"end": [
- 8,
+ 6,
11
]
}
@@ -173,11 +183,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
3
]
}
@@ -188,11 +198,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
8
]
}
@@ -206,9 +216,27 @@
"filePaths": [
"pointer-types.go"
],
- "sha1": "2609295792db8611d8b08bbee5435b5864a2f212",
+ "patch": [
+ "diff --git a/pointer-types.go b/pointer-types.go",
+ "index 05b4659..95e685d 100644",
+ "--- a/pointer-types.go",
+ "+++ b/pointer-types.go",
+ "@@ -1,4 +1,12 @@",
+ " type (",
+ "+p1 *int",
+ "+p2 **p3",
+ "+)",
+ "+type (",
+ "+p1 *string",
+ "+p2 **p1",
+ "+)",
+ "+type (",
+ " p1 *string",
+ " p2 **p1",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "d99e6ee28aef12a358f5c2aaa3e6875731d28485"
+ "shas": "7d8cd7f79e26327a145c2e37f193db0f0aa1b49b..19578c62cd7513a2390877a56b02993533e6eb4c"
}
,{
"testCaseDescription": "go-pointer-types-delete-insert-test",
@@ -220,21 +248,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
11
]
}
@@ -247,21 +275,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -276,9 +304,23 @@
"filePaths": [
"pointer-types.go"
],
- "sha1": "d99e6ee28aef12a358f5c2aaa3e6875731d28485",
+ "patch": [
+ "diff --git a/pointer-types.go b/pointer-types.go",
+ "index 95e685d..74ff673 100644",
+ "--- a/pointer-types.go",
+ "+++ b/pointer-types.go",
+ "@@ -1,6 +1,6 @@",
+ " type (",
+ "-p1 *int",
+ "-p2 **p3",
+ "+p1 *string",
+ "+p2 **p1",
+ " )",
+ " type (",
+ " p1 *string"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a837d19f0f9758240991ed6012164f15f7fd7711"
+ "shas": "19578c62cd7513a2390877a56b02993533e6eb4c..201e8300e6cc9127cf35b7f6cd44857ac967709b"
}
,{
"testCaseDescription": "go-pointer-types-replacement-test",
@@ -290,21 +332,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
11
]
},
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
}
@@ -317,21 +359,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -346,9 +388,23 @@
"filePaths": [
"pointer-types.go"
],
- "sha1": "a837d19f0f9758240991ed6012164f15f7fd7711",
+ "patch": [
+ "diff --git a/pointer-types.go b/pointer-types.go",
+ "index 74ff673..95e685d 100644",
+ "--- a/pointer-types.go",
+ "+++ b/pointer-types.go",
+ "@@ -1,6 +1,6 @@",
+ " type (",
+ "-p1 *string",
+ "-p2 **p1",
+ "+p1 *int",
+ "+p2 **p3",
+ " )",
+ " type (",
+ " p1 *string"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a1e6dddea2e8e7a0581e8c7886365eb4bd84ffe5"
+ "shas": "201e8300e6cc9127cf35b7f6cd44857ac967709b..9ba75e4b5fa06381da78759652306dc43d764bc1"
}
,{
"testCaseDescription": "go-pointer-types-delete-replacement-test",
@@ -359,11 +415,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -374,11 +430,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
}
@@ -389,11 +445,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -404,11 +460,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -419,11 +475,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
3
]
}
@@ -434,11 +490,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
5
],
"end": [
- 8,
+ 6,
11
]
}
@@ -449,11 +505,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
3
]
}
@@ -464,11 +520,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
8
]
}
@@ -479,11 +535,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
3
]
}
@@ -494,11 +550,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
5
],
"end": [
- 8,
+ 6,
8
]
}
@@ -509,11 +565,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
3
]
}
@@ -524,11 +580,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
8
]
}
@@ -542,9 +598,29 @@
"filePaths": [
"pointer-types.go"
],
- "sha1": "a1e6dddea2e8e7a0581e8c7886365eb4bd84ffe5",
+ "patch": [
+ "diff --git a/pointer-types.go b/pointer-types.go",
+ "index 95e685d..4556eeb 100644",
+ "--- a/pointer-types.go",
+ "+++ b/pointer-types.go",
+ "@@ -1,12 +1,8 @@",
+ " type (",
+ "-p1 *int",
+ "-p2 **p3",
+ "-)",
+ "-type (",
+ " p1 *string",
+ " p2 **p1",
+ " )",
+ " type (",
+ "-p1 *string",
+ "-p2 **p1",
+ "+p1 *int",
+ "+p2 **p3",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "390441dc9a8726ab3ff62efe6e9da7915745fc6f"
+ "shas": "9ba75e4b5fa06381da78759652306dc43d764bc1..31542ede38bd2367c39c2a2c74a8b5663de97b56"
}
,{
"testCaseDescription": "go-pointer-types-delete-test",
@@ -555,11 +631,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -570,11 +646,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
11
]
}
@@ -585,11 +661,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -600,11 +676,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -618,9 +694,23 @@
"filePaths": [
"pointer-types.go"
],
- "sha1": "390441dc9a8726ab3ff62efe6e9da7915745fc6f",
+ "patch": [
+ "diff --git a/pointer-types.go b/pointer-types.go",
+ "index 4556eeb..5d13f48 100644",
+ "--- a/pointer-types.go",
+ "+++ b/pointer-types.go",
+ "@@ -1,8 +1,4 @@",
+ " type (",
+ "-p1 *string",
+ "-p2 **p1",
+ "-)",
+ "-type (",
+ " p1 *int",
+ " p2 **p3",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e75361609b9f93258981f716b33bdec73f2777ae"
+ "shas": "31542ede38bd2367c39c2a2c74a8b5663de97b56..0d8c55cd851c0e65a5ba9d03a2bba90ee6301ade"
}
,{
"testCaseDescription": "go-pointer-types-delete-rest-test",
@@ -631,11 +721,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
3
]
}
@@ -646,11 +736,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
}
@@ -661,11 +751,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
3
]
}
@@ -676,11 +766,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -694,7 +784,17 @@
"filePaths": [
"pointer-types.go"
],
- "sha1": "e75361609b9f93258981f716b33bdec73f2777ae",
+ "patch": [
+ "diff --git a/pointer-types.go b/pointer-types.go",
+ "index 5d13f48..e69de29 100644",
+ "--- a/pointer-types.go",
+ "+++ b/pointer-types.go",
+ "@@ -1,4 +0,0 @@",
+ "-type (",
+ "-p1 *int",
+ "-p2 **p3",
+ "-)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "9b11035ae1a210fb170ae96625f8e899d4d25b2f"
+ "shas": "0d8c55cd851c0e65a5ba9d03a2bba90ee6301ade..bf799eac39c8188d30ac10bed1218975e6ad803c"
}]
diff --git a/test/corpus/diff-summaries/go/qualified-types.json b/test/corpus/diff-summaries/go/qualified-types.json
index fdefd8007..d8b357db5 100644
--- a/test/corpus/diff-summaries/go/qualified-types.json
+++ b/test/corpus/diff-summaries/go/qualified-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
}
@@ -55,9 +55,16 @@
"filePaths": [
"qualified-types.go"
],
- "sha1": "07104070f6fbb41df4ca2bfb623637db5ce223eb",
+ "patch": [
+ "diff --git a/qualified-types.go b/qualified-types.go",
+ "index e69de29..7840cac 100644",
+ "--- a/qualified-types.go",
+ "+++ b/qualified-types.go",
+ "@@ -0,0 +1 @@",
+ "+type a b.c"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "75ee6b013a64337b30d7a9d77f7b9a643b016f66"
+ "shas": "8b892c06025823500a32131e0005fe5ea0511bd9..cc9434572a9cf4dbb372c73f9f746edbbe46ddb2"
}
,{
"testCaseDescription": "go-qualified-types-replacement-insert-test",
@@ -68,11 +75,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -83,11 +90,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -98,11 +105,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
}
@@ -113,11 +120,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -128,11 +135,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
}
@@ -143,11 +150,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -161,9 +168,18 @@
"filePaths": [
"qualified-types.go"
],
- "sha1": "75ee6b013a64337b30d7a9d77f7b9a643b016f66",
+ "patch": [
+ "diff --git a/qualified-types.go b/qualified-types.go",
+ "index 7840cac..0256b29 100644",
+ "--- a/qualified-types.go",
+ "+++ b/qualified-types.go",
+ "@@ -1 +1,3 @@",
+ "+type x y.z",
+ "+type a b.c",
+ " type a b.c"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "69c54a54eedf5fe8a2a871dd2a5a09f8e9f21f7f"
+ "shas": "cc9434572a9cf4dbb372c73f9f746edbbe46ddb2..45ca504c2b13f39fb13a318350ce73ee051ded0a"
}
,{
"testCaseDescription": "go-qualified-types-delete-insert-test",
@@ -175,21 +191,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -202,21 +218,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
},
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -229,21 +245,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
},
{
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
}
@@ -258,9 +274,19 @@
"filePaths": [
"qualified-types.go"
],
- "sha1": "69c54a54eedf5fe8a2a871dd2a5a09f8e9f21f7f",
+ "patch": [
+ "diff --git a/qualified-types.go b/qualified-types.go",
+ "index 0256b29..e963dfd 100644",
+ "--- a/qualified-types.go",
+ "+++ b/qualified-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-type x y.z",
+ "+type a b.c",
+ " type a b.c",
+ " type a b.c"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c75f6a304a1800e1316820d2276786724ef76d24"
+ "shas": "45ca504c2b13f39fb13a318350ce73ee051ded0a..1ca51b82d0783636e0e4a89c86d5e1f3d403f641"
}
,{
"testCaseDescription": "go-qualified-types-replacement-test",
@@ -272,21 +298,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -299,21 +325,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
},
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -326,21 +352,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
},
{
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
}
@@ -355,9 +381,19 @@
"filePaths": [
"qualified-types.go"
],
- "sha1": "c75f6a304a1800e1316820d2276786724ef76d24",
+ "patch": [
+ "diff --git a/qualified-types.go b/qualified-types.go",
+ "index e963dfd..0256b29 100644",
+ "--- a/qualified-types.go",
+ "+++ b/qualified-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-type a b.c",
+ "+type x y.z",
+ " type a b.c",
+ " type a b.c"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "eb04e3d75fd1cbf8d9859e938313e1be66994f11"
+ "shas": "1ca51b82d0783636e0e4a89c86d5e1f3d403f641..cef08f468e0b80e81570eeff49e1aaf2f0819257"
}
,{
"testCaseDescription": "go-qualified-types-delete-replacement-test",
@@ -368,11 +404,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -383,11 +419,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -398,11 +434,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
}
@@ -413,11 +449,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -428,11 +464,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
}
@@ -443,11 +479,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -458,11 +494,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -473,11 +509,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
}
@@ -488,11 +524,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -506,9 +542,19 @@
"filePaths": [
"qualified-types.go"
],
- "sha1": "eb04e3d75fd1cbf8d9859e938313e1be66994f11",
+ "patch": [
+ "diff --git a/qualified-types.go b/qualified-types.go",
+ "index 0256b29..4525e0a 100644",
+ "--- a/qualified-types.go",
+ "+++ b/qualified-types.go",
+ "@@ -1,3 +1,2 @@",
+ "-type x y.z",
+ "-type a b.c",
+ " type a b.c",
+ "+type x y.z"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a1b8b1799e887e65a2962f74535fa3147a7f972f"
+ "shas": "cef08f468e0b80e81570eeff49e1aaf2f0819257..4749e1e8204299ef1dfe4ee61031f3f5b29e9763"
}
,{
"testCaseDescription": "go-qualified-types-delete-test",
@@ -519,11 +565,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -534,11 +580,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -549,11 +595,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
}
@@ -567,9 +613,17 @@
"filePaths": [
"qualified-types.go"
],
- "sha1": "a1b8b1799e887e65a2962f74535fa3147a7f972f",
+ "patch": [
+ "diff --git a/qualified-types.go b/qualified-types.go",
+ "index 4525e0a..f31a963 100644",
+ "--- a/qualified-types.go",
+ "+++ b/qualified-types.go",
+ "@@ -1,2 +1 @@",
+ "-type a b.c",
+ " type x y.z"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "97dc17cc5dc2739e249cfdcbd5c169030f7e6751"
+ "shas": "4749e1e8204299ef1dfe4ee61031f3f5b29e9763..7b55badd2f0f41090564ea56d00e8ffd57fda98f"
}
,{
"testCaseDescription": "go-qualified-types-delete-rest-test",
@@ -580,11 +634,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -595,11 +649,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -610,11 +664,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
}
@@ -628,7 +682,14 @@
"filePaths": [
"qualified-types.go"
],
- "sha1": "97dc17cc5dc2739e249cfdcbd5c169030f7e6751",
+ "patch": [
+ "diff --git a/qualified-types.go b/qualified-types.go",
+ "index f31a963..e69de29 100644",
+ "--- a/qualified-types.go",
+ "+++ b/qualified-types.go",
+ "@@ -1 +0,0 @@",
+ "-type x y.z"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "6d7202f99aff5a0fefda7df058917f141335424f"
+ "shas": "7b55badd2f0f41090564ea56d00e8ffd57fda98f..96ee23366cb8e34e0b1aef14810c83f5066a6f3b"
}]
diff --git a/test/corpus/diff-summaries/go/rune-literals.json b/test/corpus/diff-summaries/go/rune-literals.json
index 62cb6eb97..6ac2529fe 100644
--- a/test/corpus/diff-summaries/go/rune-literals.json
+++ b/test/corpus/diff-summaries/go/rune-literals.json
@@ -7,16 +7,31 @@
"span": {
"insert": {
"start": [
- 3,
+ 2,
1
],
"end": [
- 11,
+ 2,
2
]
}
},
- "summary": "Added the 'a' variable"
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ''0'' rune_literal"
},
{
"span": {
@@ -26,71 +41,173 @@
1
],
"end": [
- 11,
+ 3,
2
]
}
},
- "summary": "Added the 'b' variable"
+ "summary": "Added the 'b' identifier"
},
{
"span": {
"insert": {
"start": [
3,
- 1
+ 5
],
"end": [
- 11,
- 2
+ 3,
+ 9
]
}
},
- "summary": "Added the 'c' variable"
+ "summary": "Added the ''\\''' rune_literal"
},
{
"span": {
"insert": {
"start": [
- 3,
+ 4,
1
],
"end": [
- 11,
+ 4,
2
]
}
},
- "summary": "Added the 'c' variable"
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 5
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 5
+ ],
+ "end": [
+ 7,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the ''\\u0000'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 1
+ ],
+ "end": [
+ 8,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 5
+ ],
+ "end": [
+ 8,
+ 17
+ ]
+ }
+ },
+ "summary": "Added the ''\\U01234567'' rune_literal"
}
]
},
- "errors": {
- "rune-literals.go": [
- {
- "span": {
- "insert": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Added the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 3, column 1 - line 11, column 2"
- }
- ]
- }
+ "errors": {}
},
"filePaths": [
"rune-literals.go"
],
- "sha1": "a70b7582c8f3a84eac215e17fbe07868510577b3",
+ "patch": [
+ "diff --git a/rune-literals.go b/rune-literals.go",
+ "index e69de29..23506f8 100644",
+ "--- a/rune-literals.go",
+ "+++ b/rune-literals.go",
+ "@@ -0,0 +1,9 @@",
+ "+const (",
+ "+a = '0'",
+ "+b = '\\''",
+ "+c = '\\'",
+ "+c = '",
+ "+'",
+ "+c = '\\u0000'",
+ "+c = '\\U01234567'",
+ "+)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "cf6b204a6c6efc9314b6b2a035f42a6fa144b70c"
+ "shas": "c39ed98d50a7d8637ad13d6581d0d0d6a4bd083d..5bb2df3762d7788775b4a021c0de5a8464e87c55"
}
,{
"testCaseDescription": "go-rune-literals-replacement-insert-test",
@@ -101,11 +218,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
2
]
}
@@ -116,11 +233,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
2
]
}
@@ -131,11 +248,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
2
]
}
@@ -146,11 +263,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
1
],
"end": [
- 20,
+ 18,
2
]
}
@@ -161,11 +278,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
1
],
"end": [
- 20,
+ 18,
2
]
}
@@ -176,11 +293,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
1
],
"end": [
- 20,
+ 18,
2
]
}
@@ -191,16 +308,256 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
1
],
"end": [
- 20,
+ 18,
2
]
}
},
"summary": "Added the 'c' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'a' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'b' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''0'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\''' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 5
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 5
+ ],
+ "end": [
+ 7,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\u0000'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 1
+ ],
+ "end": [
+ 8,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 5
+ ],
+ "end": [
+ 8,
+ 17
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\U01234567'' rune_literal"
}
]
},
@@ -210,31 +567,46 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
2
]
}
},
- "summary": "Added the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 3, column 1 - line 11, column 2"
+ "summary": "Added the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 1, column 1 - line 9, column 2"
},
{
"span": {
"insert": {
"start": [
- 12,
+ 10,
1
],
"end": [
- 20,
+ 18,
2
]
}
},
- "summary": "Added the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 12, column 1 - line 20, column 2"
+ "summary": "Added the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 10, column 1 - line 18, column 2"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 19, column 1 - line 27, column 2"
}
]
}
@@ -242,9 +614,37 @@
"filePaths": [
"rune-literals.go"
],
- "sha1": "cf6b204a6c6efc9314b6b2a035f42a6fa144b70c",
+ "patch": [
+ "diff --git a/rune-literals.go b/rune-literals.go",
+ "index 23506f8..b369e37 100644",
+ "--- a/rune-literals.go",
+ "+++ b/rune-literals.go",
+ "@@ -1,4 +1,22 @@",
+ " const (",
+ "+a = '1'",
+ "+b = '",
+ "+''",
+ "+c = '\\u0011'",
+ "+c = '\\'",
+ "+c = '\\u0022'",
+ "+c = '\\U01234568'",
+ "+)",
+ "+const (",
+ "+a = '0'",
+ "+b = '\\''",
+ "+c = '\\'",
+ "+c = '",
+ "+'",
+ "+c = '\\u0000'",
+ "+c = '\\U01234567'",
+ "+)",
+ "+const (",
+ " a = '0'",
+ " b = '\\''",
+ " c = '\\'"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "55ba52157f6291f9e1ef5e52f35bafdc3d6a725c"
+ "shas": "5bb2df3762d7788775b4a021c0de5a8464e87c55..d689e07de6401ae64d5bf4467d8d89e0dca9930b"
}
,{
"testCaseDescription": "go-rune-literals-delete-insert-test",
@@ -253,30 +653,33 @@
"rune-literals.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 4,
- 5
- ],
- "end": [
- 4,
- 8
- ]
- },
- {
- "start": [
- 4,
- 5
- ],
- "end": [
- 4,
- 8
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
},
- "summary": "Replaced the ''1'' rune_literal with the ''0'' rune_literal in the a variable of the 'main' module"
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ''0'' rune_literal"
},
{
"span": {
@@ -286,18 +689,168 @@
1
],
"end": [
- 11,
+ 3,
2
]
}
},
- "summary": "Added the 'b' variable"
+ "summary": "Added the 'b' identifier"
},
{
"span": {
"insert": {
"start": [
3,
+ 5
+ ],
+ "end": [
+ 3,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the ''\\''' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 5
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 5
+ ],
+ "end": [
+ 7,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the ''\\u0000'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 1
+ ],
+ "end": [
+ 8,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 5
+ ],
+ "end": [
+ 8,
+ 17
+ ]
+ }
+ },
+ "summary": "Added the ''\\U01234567'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 1
+ ],
+ "end": [
+ 10,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ')\nconst (' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 11,
1
],
"end": [
@@ -306,32 +859,392 @@
]
}
},
- "summary": "Added the 'c' variable"
+ "summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
- 3,
- 1
+ 11,
+ 5
],
"end": [
11,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ''0'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 12,
+ 1
+ ],
+ "end": [
+ 12,
2
]
}
},
- "summary": "Added the 'c' variable"
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 12,
+ 5
+ ],
+ "end": [
+ 12,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the ''\\''' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 13,
+ 1
+ ],
+ "end": [
+ 13,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 13,
+ 5
+ ],
+ "end": [
+ 13,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 14,
+ 1
+ ],
+ "end": [
+ 14,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 14,
+ 5
+ ],
+ "end": [
+ 15,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 16,
+ 1
+ ],
+ "end": [
+ 16,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 16,
+ 5
+ ],
+ "end": [
+ 16,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the ''\\u0000'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 17,
+ 1
+ ],
+ "end": [
+ 17,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 17,
+ 5
+ ],
+ "end": [
+ 17,
+ 17
+ ]
+ }
+ },
+ "summary": "Added the ''\\U01234567'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 18,
+ 1
+ ],
+ "end": [
+ 19,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ')\nconst (' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 20,
+ 1
+ ],
+ "end": [
+ 20,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 20,
+ 5
+ ],
+ "end": [
+ 20,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ''0'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 21,
+ 1
+ ],
+ "end": [
+ 21,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 21,
+ 5
+ ],
+ "end": [
+ 21,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the ''\\''' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 22,
+ 1
+ ],
+ "end": [
+ 22,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 22,
+ 5
+ ],
+ "end": [
+ 22,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 23,
+ 1
+ ],
+ "end": [
+ 23,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 23,
+ 5
+ ],
+ "end": [
+ 24,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 25,
+ 1
+ ],
+ "end": [
+ 25,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 25,
+ 5
+ ],
+ "end": [
+ 25,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the ''\\u0000'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 26,
+ 1
+ ],
+ "end": [
+ 26,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 26,
+ 5
+ ],
+ "end": [
+ 26,
+ 17
+ ]
+ }
+ },
+ "summary": "Added the ''\\U01234567'' rune_literal"
},
{
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 9,
2
]
}
@@ -342,11 +1255,131 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
2
]
}
@@ -359,33 +1392,48 @@
"rune-literals.go": [
{
"span": {
- "insert": {
+ "delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
2
]
}
},
- "summary": "Added the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 3, column 1 - line 11, column 2"
+ "summary": "Deleted the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 1, column 1 - line 9, column 2"
},
{
"span": {
"delete": {
"start": [
- 3,
+ 10,
1
],
"end": [
- 11,
+ 18,
2
]
}
},
- "summary": "Deleted the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 3, column 1 - line 11, column 2"
+ "summary": "Deleted the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 10, column 1 - line 18, column 2"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 19, column 1 - line 27, column 2"
}
]
}
@@ -393,280 +1441,47 @@
"filePaths": [
"rune-literals.go"
],
- "sha1": "55ba52157f6291f9e1ef5e52f35bafdc3d6a725c",
+ "patch": [
+ "diff --git a/rune-literals.go b/rune-literals.go",
+ "index b369e37..aabbad7 100644",
+ "--- a/rune-literals.go",
+ "+++ b/rune-literals.go",
+ "@@ -1,11 +1,11 @@",
+ " const (",
+ "-a = '1'",
+ "-b = '",
+ "-''",
+ "-c = '\\u0011'",
+ "+a = '0'",
+ "+b = '\\''",
+ " c = '\\'",
+ "-c = '\\u0022'",
+ "-c = '\\U01234568'",
+ "+c = '",
+ "+'",
+ "+c = '\\u0000'",
+ "+c = '\\U01234567'",
+ " )",
+ " const (",
+ " a = '0'"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "2641262d253b06cce5bb3cadc74b7d2a6ce4eecb"
+ "shas": "d689e07de6401ae64d5bf4467d8d89e0dca9930b..69b60b0054e8d0504ebf6ad05fefea28948036ab"
}
,{
"testCaseDescription": "go-rune-literals-replacement-test",
"expectedResult": {
"changes": {
"rune-literals.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
- 5
- ],
- "end": [
- 4,
- 8
- ]
- },
- {
- "start": [
- 4,
- 5
- ],
- "end": [
- 4,
- 8
- ]
- }
- ]
- },
- "summary": "Replaced the ''0'' rune_literal with the ''1'' rune_literal in the a variable of the 'main' module"
- },
{
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Added the 'c' variable"
- },
- {
- "span": {
- "insert": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Added the 'c' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Deleted the 'b' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Deleted the 'c' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Deleted the 'c' variable"
- }
- ]
- },
- "errors": {
- "rune-literals.go": [
- {
- "span": {
- "insert": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Added the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 3, column 1 - line 11, column 2"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Deleted the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 3, column 1 - line 11, column 2"
- }
- ]
- }
- },
- "filePaths": [
- "rune-literals.go"
- ],
- "sha1": "2641262d253b06cce5bb3cadc74b7d2a6ce4eecb",
- "gitDir": "test/corpus/repos/go",
- "sha2": "b868792d212d4083350fd4d4afb2fc9a7bad2d80"
-}
-,{
- "testCaseDescription": "go-rune-literals-delete-replacement-test",
- "expectedResult": {
- "changes": {
- "rune-literals.go": [
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Deleted the 'a' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Deleted the 'c' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Deleted the 'c' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 12,
- 1
- ],
- "end": [
- 20,
- 2
- ]
- }
- },
- "summary": "Deleted the 'a' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 12,
- 1
- ],
- "end": [
- 20,
- 2
- ]
- }
- },
- "summary": "Deleted the 'b' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 12,
- 1
- ],
- "end": [
- 20,
- 2
- ]
- }
- },
- "summary": "Deleted the 'c' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 12,
- 1
- ],
- "end": [
- 20,
- 2
- ]
- }
- },
- "summary": "Deleted the 'c' variable"
- },
- {
- "span": {
- "insert": {
- "start": [
- 12,
- 1
- ],
- "end": [
- 20,
+ 9,
2
]
}
@@ -677,11 +1492,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 1,
1
],
"end": [
- 20,
+ 9,
2
]
}
@@ -691,17 +1506,707 @@
{
"span": {
"insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 9,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'a' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'b' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'a' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'b' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''0'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\''' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 5
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 5
+ ],
+ "end": [
+ 7,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\u0000'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 1
+ ],
+ "end": [
+ 8,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 5
+ ],
+ "end": [
+ 8,
+ 17
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\U01234567'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 9,
+ 1
+ ],
+ "end": [
+ 10,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ')\nconst (' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 11,
+ 1
+ ],
+ "end": [
+ 11,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 11,
+ 5
+ ],
+ "end": [
+ 11,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''0'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
"start": [
12,
1
],
+ "end": [
+ 12,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 12,
+ 5
+ ],
+ "end": [
+ 12,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\''' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 13,
+ 1
+ ],
+ "end": [
+ 13,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 13,
+ 5
+ ],
+ "end": [
+ 13,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 14,
+ 1
+ ],
+ "end": [
+ 14,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 14,
+ 5
+ ],
+ "end": [
+ 15,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 16,
+ 1
+ ],
+ "end": [
+ 16,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 16,
+ 5
+ ],
+ "end": [
+ 16,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\u0000'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 17,
+ 1
+ ],
+ "end": [
+ 17,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 17,
+ 5
+ ],
+ "end": [
+ 17,
+ 17
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\U01234567'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 18,
+ 1
+ ],
+ "end": [
+ 19,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ')\nconst (' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 20,
+ 1
+ ],
"end": [
20,
2
]
}
},
- "summary": "Added the 'c' variable"
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 20,
+ 5
+ ],
+ "end": [
+ 20,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''0'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 21,
+ 1
+ ],
+ "end": [
+ 21,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 21,
+ 5
+ ],
+ "end": [
+ 21,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\''' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 22,
+ 1
+ ],
+ "end": [
+ 22,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 22,
+ 5
+ ],
+ "end": [
+ 22,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 23,
+ 1
+ ],
+ "end": [
+ 23,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 23,
+ 5
+ ],
+ "end": [
+ 24,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 25,
+ 1
+ ],
+ "end": [
+ 25,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 25,
+ 5
+ ],
+ "end": [
+ 25,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\u0000'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 26,
+ 1
+ ],
+ "end": [
+ 26,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 26,
+ 5
+ ],
+ "end": [
+ 26,
+ 17
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\U01234567'' rune_literal"
}
]
},
@@ -709,33 +2214,311 @@
"rune-literals.go": [
{
"span": {
- "delete": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 9,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 1, column 1 - line 9, column 2"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 10, column 1 - line 18, column 2"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 19, column 1 - line 27, column 2"
+ }
+ ]
+ }
+ },
+ "filePaths": [
+ "rune-literals.go"
+ ],
+ "patch": [
+ "diff --git a/rune-literals.go b/rune-literals.go",
+ "index aabbad7..b369e37 100644",
+ "--- a/rune-literals.go",
+ "+++ b/rune-literals.go",
+ "@@ -1,11 +1,11 @@",
+ " const (",
+ "-a = '0'",
+ "-b = '\\''",
+ "+a = '1'",
+ "+b = '",
+ "+''",
+ "+c = '\\u0011'",
+ " c = '\\'",
+ "-c = '",
+ "-'",
+ "-c = '\\u0000'",
+ "-c = '\\U01234567'",
+ "+c = '\\u0022'",
+ "+c = '\\U01234568'",
+ " )",
+ " const (",
+ " a = '0'"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "69b60b0054e8d0504ebf6ad05fefea28948036ab..82a3e6fb5cfd43f8fd5fc730e8803d9a7f5cfba1"
+}
+,{
+ "testCaseDescription": "go-rune-literals-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rune-literals.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ''0'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
"start": [
3,
1
],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the ''\\''' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 5
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 5
+ ],
+ "end": [
+ 7,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the ''\\u0000'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 1
+ ],
+ "end": [
+ 8,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 5
+ ],
+ "end": [
+ 8,
+ 17
+ ]
+ }
+ },
+ "summary": "Added the ''\\U01234567'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 1
+ ],
+ "end": [
+ 10,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ')\nconst (' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 11,
+ 1
+ ],
"end": [
11,
2
]
}
},
- "summary": "Deleted the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 3, column 1 - line 11, column 2"
+ "summary": "Added the 'a' identifier"
},
{
"span": {
- "delete": {
+ "insert": {
"start": [
- 12,
- 1
+ 11,
+ 5
],
"end": [
- 20,
- 2
+ 11,
+ 8
]
}
},
- "summary": "Deleted the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 12, column 1 - line 20, column 2"
+ "summary": "Added the ''1'' rune_literal"
},
{
"span": {
@@ -745,37 +2528,172 @@
1
],
"end": [
- 20,
+ 12,
2
]
}
},
- "summary": "Added the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 12, column 1 - line 20, column 2"
- }
- ]
- }
- },
- "filePaths": [
- "rune-literals.go"
- ],
- "sha1": "b868792d212d4083350fd4d4afb2fc9a7bad2d80",
- "gitDir": "test/corpus/repos/go",
- "sha2": "23792f81b6b29fb055224aa60c02e96a1d3d6228"
-}
-,{
- "testCaseDescription": "go-rune-literals-delete-test",
- "expectedResult": {
- "changes": {
- "rune-literals.go": [
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 12,
+ 5
+ ],
+ "end": [
+ 13,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 13,
+ 2
+ ],
+ "end": [
+ 14,
+ 1
+ ]
+ }
+ },
+ "summary": "Added the ''\n' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 14,
+ 1
+ ],
+ "end": [
+ 14,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 14,
+ 5
+ ],
+ "end": [
+ 14,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the ''\\u0011'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 15,
+ 1
+ ],
+ "end": [
+ 15,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 15,
+ 5
+ ],
+ "end": [
+ 15,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 16,
+ 1
+ ],
+ "end": [
+ 16,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 16,
+ 5
+ ],
+ "end": [
+ 16,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the ''\\u0022'' rune_literal"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 17,
+ 1
+ ],
+ "end": [
+ 17,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 17,
+ 5
+ ],
+ "end": [
+ 17,
+ 17
+ ]
+ }
+ },
+ "summary": "Added the ''\\U01234568'' rune_literal"
+ },
{
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
2
]
}
@@ -786,26 +2704,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
- 2
- ]
- }
- },
- "summary": "Deleted the 'b' variable"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 11,
+ 9,
2
]
}
@@ -816,11 +2719,131 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
2
]
}
@@ -831,6 +2854,178 @@
},
"errors": {
"rune-literals.go": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 9,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 1, column 1 - line 9, column 2"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 10,
+ 1
+ ],
+ "end": [
+ 18,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 10, column 1 - line 18, column 2"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 19,
+ 1
+ ],
+ "end": [
+ 27,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 19, column 1 - line 27, column 2"
+ }
+ ]
+ }
+ },
+ "filePaths": [
+ "rune-literals.go"
+ ],
+ "patch": [
+ "diff --git a/rune-literals.go b/rune-literals.go",
+ "index b369e37..34c7a16 100644",
+ "--- a/rune-literals.go",
+ "+++ b/rune-literals.go",
+ "@@ -1,13 +1,4 @@",
+ " const (",
+ "-a = '1'",
+ "-b = '",
+ "-''",
+ "-c = '\\u0011'",
+ "-c = '\\'",
+ "-c = '\\u0022'",
+ "-c = '\\U01234568'",
+ "-)",
+ "-const (",
+ " a = '0'",
+ " b = '\\''",
+ " c = '\\'",
+ "@@ -17,11 +8,11 @@ c = '\\u0000'",
+ " c = '\\U01234567'",
+ " )",
+ " const (",
+ "-a = '0'",
+ "-b = '\\''",
+ "+a = '1'",
+ "+b = '",
+ "+''",
+ "+c = '\\u0011'",
+ " c = '\\'",
+ "-c = '",
+ "-'",
+ "-c = '\\u0000'",
+ "-c = '\\U01234567'",
+ "+c = '\\u0022'",
+ "+c = '\\U01234568'",
+ " )"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "82a3e6fb5cfd43f8fd5fc730e8803d9a7f5cfba1..8ed6f66fd14bf48fb6413774648827afdbd8c159"
+}
+,{
+ "testCaseDescription": "go-rune-literals-delete-test",
+ "expectedResult": {
+ "changes": {
+ "rune-literals.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 9,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'a' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 9,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 9,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'c' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''0'' rune_literal"
+ },
{
"span": {
"delete": {
@@ -838,13 +3033,377 @@
3,
1
],
+ "end": [
+ 3,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\''' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 5
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 5
+ ],
+ "end": [
+ 7,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\u0000'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 1
+ ],
+ "end": [
+ 8,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 5
+ ],
+ "end": [
+ 8,
+ 17
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\U01234567'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 9,
+ 1
+ ],
+ "end": [
+ 10,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ')\nconst (' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 11,
+ 1
+ ],
"end": [
11,
2
]
}
},
- "summary": "Deleted the 'const (\na = '0'\nb = '\\''\nc = '\\'\nc = '\n'\nc = '\\u0000'\nc = '\\U01234567'\n)' at line 3, column 1 - line 11, column 2"
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 11,
+ 5
+ ],
+ "end": [
+ 11,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''1'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 12,
+ 1
+ ],
+ "end": [
+ 12,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 12,
+ 5
+ ],
+ "end": [
+ 13,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 13,
+ 2
+ ],
+ "end": [
+ 14,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 14,
+ 1
+ ],
+ "end": [
+ 14,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 14,
+ 5
+ ],
+ "end": [
+ 14,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\u0011'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 15,
+ 1
+ ],
+ "end": [
+ 15,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 15,
+ 5
+ ],
+ "end": [
+ 15,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\'' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 16,
+ 1
+ ],
+ "end": [
+ 16,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 16,
+ 5
+ ],
+ "end": [
+ 16,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\u0022'' rune_literal"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 17,
+ 1
+ ],
+ "end": [
+ 17,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 17,
+ 5
+ ],
+ "end": [
+ 17,
+ 17
+ ]
+ }
+ },
+ "summary": "Deleted the ''\\U01234568'' rune_literal"
+ }
+ ]
+ },
+ "errors": {
+ "rune-literals.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 9,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 1, column 1 - line 9, column 2"
}
]
}
@@ -852,9 +3411,28 @@
"filePaths": [
"rune-literals.go"
],
- "sha1": "23792f81b6b29fb055224aa60c02e96a1d3d6228",
+ "patch": [
+ "diff --git a/rune-literals.go b/rune-literals.go",
+ "index 34c7a16..dc07d00 100644",
+ "--- a/rune-literals.go",
+ "+++ b/rune-literals.go",
+ "@@ -1,13 +1,4 @@",
+ " const (",
+ "-a = '0'",
+ "-b = '\\''",
+ "-c = '\\'",
+ "-c = '",
+ "-'",
+ "-c = '\\u0000'",
+ "-c = '\\U01234567'",
+ "-)",
+ "-const (",
+ " a = '1'",
+ " b = '",
+ " ''"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "0b1cadf8e014685e276cc779ebb0a894a9ac3fd1"
+ "shas": "8ed6f66fd14bf48fb6413774648827afdbd8c159..40ed8ece89b9b38ab0ca6cd469486b874b187042"
}
,{
"testCaseDescription": "go-rune-literals-delete-rest-test",
@@ -865,11 +3443,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
2
]
}
@@ -880,11 +3458,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
2
]
}
@@ -895,11 +3473,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
2
]
}
@@ -914,16 +3492,16 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 11,
+ 9,
2
]
}
},
- "summary": "Deleted the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 3, column 1 - line 11, column 2"
+ "summary": "Deleted the 'const (\na = '1'\nb = '\n''\nc = '\\u0011'\nc = '\\'\nc = '\\u0022'\nc = '\\U01234568'\n)' at line 1, column 1 - line 9, column 2"
}
]
}
@@ -931,7 +3509,22 @@
"filePaths": [
"rune-literals.go"
],
- "sha1": "0b1cadf8e014685e276cc779ebb0a894a9ac3fd1",
+ "patch": [
+ "diff --git a/rune-literals.go b/rune-literals.go",
+ "index dc07d00..e69de29 100644",
+ "--- a/rune-literals.go",
+ "+++ b/rune-literals.go",
+ "@@ -1,9 +0,0 @@",
+ "-const (",
+ "-a = '1'",
+ "-b = '",
+ "-''",
+ "-c = '\\u0011'",
+ "-c = '\\'",
+ "-c = '\\u0022'",
+ "-c = '\\U01234568'",
+ "-)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "6a5c5e925499fc0ac05bc20d3440592bebc89ea5"
+ "shas": "40ed8ece89b9b38ab0ca6cd469486b874b187042..6761a7543f7002279b3e1d53f388c0b6408e11ac"
}]
diff --git a/test/corpus/diff-summaries/go/select-statements.json b/test/corpus/diff-summaries/go/select-statements.json
index 133e537e6..f3c945bdd 100644
--- a/test/corpus/diff-summaries/go/select-statements.json
+++ b/test/corpus/diff-summaries/go/select-statements.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
15
],
"end": [
- 4,
+ 2,
16
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
12
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
13
],
"end": [
- 5,
+ 3,
14
]
}
@@ -67,11 +67,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
}
@@ -82,11 +82,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
13
],
"end": [
- 6,
+ 4,
14
]
}
@@ -97,11 +97,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
12
]
}
@@ -112,11 +112,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
13
],
"end": [
- 7,
+ 5,
14
]
}
@@ -127,11 +127,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
10
],
"end": [
- 8,
+ 6,
14
]
}
@@ -142,11 +142,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
15
],
"end": [
- 8,
+ 6,
20
]
}
@@ -157,11 +157,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
21
],
"end": [
- 8,
+ 6,
22
]
}
@@ -172,11 +172,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
5
],
"end": [
- 9,
+ 7,
12
]
}
@@ -187,11 +187,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
13
],
"end": [
- 9,
+ 7,
14
]
}
@@ -202,11 +202,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
3
],
"end": [
- 10,
+ 8,
10
]
}
@@ -217,11 +217,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
5
],
"end": [
- 11,
+ 9,
11
]
}
@@ -235,9 +235,25 @@
"filePaths": [
"select-statements.go"
],
- "sha1": "55c9268038cdb6e46dd211683ac12b462f9e590f",
+ "patch": [
+ "diff --git a/select-statements.go b/select-statements.go",
+ "index e69de29..7fe1c0b 100644",
+ "--- a/select-statements.go",
+ "+++ b/select-statements.go",
+ "@@ -0,0 +1,10 @@",
+ "+select {",
+ "+ case x := <-c:",
+ "+ println(x)",
+ "+ case y <- c:",
+ "+ println(5)",
+ "+ case <-time.After(1):",
+ "+ println(6)",
+ "+ default:",
+ "+ return",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "10ee9d2b43e7c512ee3d5465b13e689f68327003"
+ "shas": "e544e711890744c45f9b49604be9c175422f7e15..aeffeb8d68826e213ea01226ec8bc50684bdd0d9"
}
,{
"testCaseDescription": "go-select-statements-replacement-insert-test",
@@ -246,30 +262,453 @@
"select-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 13,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 2,
+ 8
+ ],
+ "end": [
+ 2,
+ 9
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 15
+ ],
+ "end": [
+ 2,
+ 16
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'println' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 13
+ ],
+ "end": [
+ 3,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the 'x' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 8
+ ],
+ "end": [
+ 4,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 13
+ ],
+ "end": [
+ 4,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 5,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'println' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 13
+ ],
+ "end": [
+ 5,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the '5'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 10
+ ],
+ "end": [
+ 6,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the 'time' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 15
+ ],
+ "end": [
+ 6,
+ 20
+ ]
+ }
+ },
+ "summary": "Added the 'After' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 21
+ ],
+ "end": [
+ 6,
+ 22
+ ]
+ }
+ },
+ "summary": "Added the '2'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 5
+ ],
+ "end": [
+ 7,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'println' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 13
+ ],
+ "end": [
+ 7,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the '6'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 3
+ ],
+ "end": [
+ 8,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'default' communication_case"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 5
+ ],
+ "end": [
+ 9,
+ 11
+ ]
+ }
+ },
+ "summary": "Added the 'empty' return statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 12,
+ 8
+ ],
+ "end": [
+ 12,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the 'x' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 12,
+ 15
+ ],
+ "end": [
+ 12,
+ 16
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 13,
+ 5
+ ],
+ "end": [
+ 13,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'println' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 13,
+ 13
+ ],
+ "end": [
+ 13,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the 'x' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 14,
+ 8
+ ],
+ "end": [
+ 14,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the 'y' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 14,
+ 13
+ ],
+ "end": [
+ 14,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 15,
+ 5
+ ],
+ "end": [
+ 15,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'println' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 15,
+ 13
+ ],
+ "end": [
+ 15,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the '5'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 16,
+ 10
+ ],
+ "end": [
+ 16,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the 'time' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 16,
+ 15
+ ],
+ "end": [
+ 16,
+ 20
+ ]
+ }
+ },
+ "summary": "Added the 'After' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 16,
+ 21
+ ],
+ "end": [
+ 16,
+ 22
+ ]
+ }
+ },
+ "summary": "Added the '1'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 17,
+ 5
+ ],
+ "end": [
+ 17,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'println' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 17,
+ 13
+ ],
+ "end": [
+ 17,
+ 14
+ ]
+ }
+ },
+ "summary": "Added the '6'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 18,
+ 3
+ ],
+ "end": [
+ 18,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'default' communication_case"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 19,
+ 5
+ ],
+ "end": [
+ 19,
+ 11
+ ]
+ }
+ },
+ "summary": "Added the 'empty' return statement"
}
]
},
@@ -278,9 +717,39 @@
"filePaths": [
"select-statements.go"
],
- "sha1": "10ee9d2b43e7c512ee3d5465b13e689f68327003",
+ "patch": [
+ "diff --git a/select-statements.go b/select-statements.go",
+ "index 7fe1c0b..1403fc7 100644",
+ "--- a/select-statements.go",
+ "+++ b/select-statements.go",
+ "@@ -1,4 +1,24 @@",
+ " select {",
+ "+ case a := <-c:",
+ "+ println(x)",
+ "+ case b <- c:",
+ "+ println(5)",
+ "+ case <-time.After(2):",
+ "+ println(6)",
+ "+ default:",
+ "+ return",
+ "+}",
+ "+select {",
+ "+ case x := <-c:",
+ "+ println(x)",
+ "+ case y <- c:",
+ "+ println(5)",
+ "+ case <-time.After(1):",
+ "+ println(6)",
+ "+ default:",
+ "+ return",
+ "+}",
+ "+select {",
+ " case x := <-c:",
+ " println(x)",
+ " case y <- c:"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "70eb607bd14f536752bf15298af7089aca4e9f0d"
+ "shas": "aeffeb8d68826e213ea01226ec8bc50684bdd0d9..092ef77661e7d72d3993aeaa0ca7d9b7d25778c2"
}
,{
"testCaseDescription": "go-select-statements-delete-insert-test",
@@ -292,21 +761,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
},
{
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
}
@@ -319,21 +788,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
},
{
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
}
@@ -346,21 +815,21 @@
"replace": [
{
"start": [
- 8,
+ 6,
21
],
"end": [
- 8,
+ 6,
22
]
},
{
"start": [
- 8,
+ 6,
21
],
"end": [
- 8,
+ 6,
22
]
}
@@ -375,9 +844,27 @@
"filePaths": [
"select-statements.go"
],
- "sha1": "70eb607bd14f536752bf15298af7089aca4e9f0d",
+ "patch": [
+ "diff --git a/select-statements.go b/select-statements.go",
+ "index 1403fc7..3e83983 100644",
+ "--- a/select-statements.go",
+ "+++ b/select-statements.go",
+ "@@ -1,9 +1,9 @@",
+ " select {",
+ "- case a := <-c:",
+ "+ case x := <-c:",
+ " println(x)",
+ "- case b <- c:",
+ "+ case y <- c:",
+ " println(5)",
+ "- case <-time.After(2):",
+ "+ case <-time.After(1):",
+ " println(6)",
+ " default:",
+ " return"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3b4e6d4c16e78a1938b465a7c629dcc0763cd0c9"
+ "shas": "092ef77661e7d72d3993aeaa0ca7d9b7d25778c2..b09f58dd4fb0e33386e161464ecc3c2b5da1306c"
}
,{
"testCaseDescription": "go-select-statements-replacement-test",
@@ -389,21 +876,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
},
{
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
}
@@ -416,21 +903,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
},
{
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
}
@@ -443,21 +930,21 @@
"replace": [
{
"start": [
- 8,
+ 6,
21
],
"end": [
- 8,
+ 6,
22
]
},
{
"start": [
- 8,
+ 6,
21
],
"end": [
- 8,
+ 6,
22
]
}
@@ -472,9 +959,27 @@
"filePaths": [
"select-statements.go"
],
- "sha1": "3b4e6d4c16e78a1938b465a7c629dcc0763cd0c9",
+ "patch": [
+ "diff --git a/select-statements.go b/select-statements.go",
+ "index 3e83983..1403fc7 100644",
+ "--- a/select-statements.go",
+ "+++ b/select-statements.go",
+ "@@ -1,9 +1,9 @@",
+ " select {",
+ "- case x := <-c:",
+ "+ case a := <-c:",
+ " println(x)",
+ "- case y <- c:",
+ "+ case b <- c:",
+ " println(5)",
+ "- case <-time.After(1):",
+ "+ case <-time.After(2):",
+ " println(6)",
+ " default:",
+ " return"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "04382b83ecd70b1e348763a51f5b3facbb1e86be"
+ "shas": "b09f58dd4fb0e33386e161464ecc3c2b5da1306c..3eccdfaeeaf42d130fd52c95bfd791027e39cf0f"
}
,{
"testCaseDescription": "go-select-statements-delete-replacement-test",
@@ -485,11 +990,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
}
@@ -500,11 +1005,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
15
],
"end": [
- 4,
+ 2,
16
]
}
@@ -515,11 +1020,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
12
]
}
@@ -530,11 +1035,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
13
],
"end": [
- 5,
+ 3,
14
]
}
@@ -545,11 +1050,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
}
@@ -560,11 +1065,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
13
],
"end": [
- 6,
+ 4,
14
]
}
@@ -575,11 +1080,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
12
]
}
@@ -590,11 +1095,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
13
],
"end": [
- 7,
+ 5,
14
]
}
@@ -605,11 +1110,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
10
],
"end": [
- 8,
+ 6,
14
]
}
@@ -620,11 +1125,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
15
],
"end": [
- 8,
+ 6,
20
]
}
@@ -635,11 +1140,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
21
],
"end": [
- 8,
+ 6,
22
]
}
@@ -650,11 +1155,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
5
],
"end": [
- 9,
+ 7,
12
]
}
@@ -665,11 +1170,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
13
],
"end": [
- 9,
+ 7,
14
]
}
@@ -680,11 +1185,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
3
],
"end": [
- 10,
+ 8,
10
]
}
@@ -695,11 +1200,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
5
],
"end": [
- 11,
+ 9,
11
]
}
@@ -710,11 +1215,11 @@
"span": {
"delete": {
"start": [
- 14,
+ 12,
8
],
"end": [
- 14,
+ 12,
9
]
}
@@ -725,11 +1230,11 @@
"span": {
"delete": {
"start": [
- 14,
+ 12,
15
],
"end": [
- 14,
+ 12,
16
]
}
@@ -740,11 +1245,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
5
],
"end": [
- 15,
+ 13,
12
]
}
@@ -755,11 +1260,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
13
],
"end": [
- 15,
+ 13,
14
]
}
@@ -770,11 +1275,11 @@
"span": {
"delete": {
"start": [
- 16,
+ 14,
8
],
"end": [
- 16,
+ 14,
9
]
}
@@ -785,11 +1290,11 @@
"span": {
"delete": {
"start": [
- 16,
+ 14,
13
],
"end": [
- 16,
+ 14,
14
]
}
@@ -800,11 +1305,11 @@
"span": {
"delete": {
"start": [
- 17,
+ 15,
5
],
"end": [
- 17,
+ 15,
12
]
}
@@ -815,11 +1320,11 @@
"span": {
"delete": {
"start": [
- 17,
+ 15,
13
],
"end": [
- 17,
+ 15,
14
]
}
@@ -830,11 +1335,11 @@
"span": {
"delete": {
"start": [
- 18,
+ 16,
10
],
"end": [
- 18,
+ 16,
14
]
}
@@ -845,11 +1350,11 @@
"span": {
"delete": {
"start": [
- 18,
+ 16,
15
],
"end": [
- 18,
+ 16,
20
]
}
@@ -860,11 +1365,11 @@
"span": {
"delete": {
"start": [
- 18,
+ 16,
21
],
"end": [
- 18,
+ 16,
22
]
}
@@ -875,11 +1380,11 @@
"span": {
"delete": {
"start": [
- 19,
+ 17,
5
],
"end": [
- 19,
+ 17,
12
]
}
@@ -890,11 +1395,11 @@
"span": {
"delete": {
"start": [
- 19,
+ 17,
13
],
"end": [
- 19,
+ 17,
14
]
}
@@ -905,11 +1410,11 @@
"span": {
"delete": {
"start": [
- 20,
+ 18,
3
],
"end": [
- 20,
+ 18,
10
]
}
@@ -920,11 +1425,11 @@
"span": {
"delete": {
"start": [
- 21,
+ 19,
5
],
"end": [
- 21,
+ 19,
11
]
}
@@ -935,11 +1440,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 12,
8
],
"end": [
- 14,
+ 12,
9
]
}
@@ -950,11 +1455,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 12,
15
],
"end": [
- 14,
+ 12,
16
]
}
@@ -965,11 +1470,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
5
],
"end": [
- 15,
+ 13,
12
]
}
@@ -980,11 +1485,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
13
],
"end": [
- 15,
+ 13,
14
]
}
@@ -995,11 +1500,11 @@
"span": {
"insert": {
"start": [
- 16,
+ 14,
8
],
"end": [
- 16,
+ 14,
9
]
}
@@ -1010,11 +1515,11 @@
"span": {
"insert": {
"start": [
- 16,
+ 14,
13
],
"end": [
- 16,
+ 14,
14
]
}
@@ -1025,11 +1530,11 @@
"span": {
"insert": {
"start": [
- 17,
+ 15,
5
],
"end": [
- 17,
+ 15,
12
]
}
@@ -1040,11 +1545,11 @@
"span": {
"insert": {
"start": [
- 17,
+ 15,
13
],
"end": [
- 17,
+ 15,
14
]
}
@@ -1055,11 +1560,11 @@
"span": {
"insert": {
"start": [
- 18,
+ 16,
10
],
"end": [
- 18,
+ 16,
14
]
}
@@ -1070,11 +1575,11 @@
"span": {
"insert": {
"start": [
- 18,
+ 16,
15
],
"end": [
- 18,
+ 16,
20
]
}
@@ -1085,11 +1590,11 @@
"span": {
"insert": {
"start": [
- 18,
+ 16,
21
],
"end": [
- 18,
+ 16,
22
]
}
@@ -1100,11 +1605,11 @@
"span": {
"insert": {
"start": [
- 19,
+ 17,
5
],
"end": [
- 19,
+ 17,
12
]
}
@@ -1115,11 +1620,11 @@
"span": {
"insert": {
"start": [
- 19,
+ 17,
13
],
"end": [
- 19,
+ 17,
14
]
}
@@ -1130,11 +1635,11 @@
"span": {
"insert": {
"start": [
- 20,
+ 18,
3
],
"end": [
- 20,
+ 18,
10
]
}
@@ -1145,11 +1650,11 @@
"span": {
"insert": {
"start": [
- 21,
+ 19,
5
],
"end": [
- 21,
+ 19,
11
]
}
@@ -1163,55 +1668,47 @@
"filePaths": [
"select-statements.go"
],
- "sha1": "04382b83ecd70b1e348763a51f5b3facbb1e86be",
+ "patch": [
+ "diff --git a/select-statements.go b/select-statements.go",
+ "index 1403fc7..234dd89 100644",
+ "--- a/select-statements.go",
+ "+++ b/select-statements.go",
+ "@@ -1,14 +1,4 @@",
+ " select {",
+ "- case a := <-c:",
+ "- println(x)",
+ "- case b <- c:",
+ "- println(5)",
+ "- case <-time.After(2):",
+ "- println(6)",
+ "- default:",
+ "- return",
+ "-}",
+ "-select {",
+ " case x := <-c:",
+ " println(x)",
+ " case y <- c:",
+ "@@ -19,11 +9,11 @@ select {",
+ " return",
+ " }",
+ " select {",
+ "- case x := <-c:",
+ "+ case a := <-c:",
+ " println(x)",
+ "- case y <- c:",
+ "+ case b <- c:",
+ " println(5)",
+ "- case <-time.After(1):",
+ "+ case <-time.After(2):",
+ " println(6)",
+ " default:",
+ " return"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "034ff171e1fa56471fd187d8dbe4633da19e4204"
+ "shas": "3eccdfaeeaf42d130fd52c95bfd791027e39cf0f..ce166d19b29200e4343c9b74fee611caf2273a62"
}
,{
"testCaseDescription": "go-select-statements-delete-test",
- "expectedResult": {
- "changes": {
- "select-statements.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 13,
- 1
- ]
- }
- ]
- },
- "summary": "Replaced the 'main' module with the 'main' module"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "select-statements.go"
- ],
- "sha1": "034ff171e1fa56471fd187d8dbe4633da19e4204",
- "gitDir": "test/corpus/repos/go",
- "sha2": "9c02793fcb2f68a293f0c4f92551c34561ec4f24"
-}
-,{
- "testCaseDescription": "go-select-statements-delete-rest-test",
"expectedResult": {
"changes": {
"select-statements.go": [
@@ -1219,26 +1716,26 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
}
},
- "summary": "Deleted the 'a' identifier"
+ "summary": "Deleted the 'x' identifier"
},
{
"span": {
"delete": {
"start": [
- 4,
+ 2,
15
],
"end": [
- 4,
+ 2,
16
]
}
@@ -1249,11 +1746,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
12
]
}
@@ -1264,11 +1761,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
13
],
"end": [
- 5,
+ 3,
14
]
}
@@ -1279,26 +1776,26 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
}
},
- "summary": "Deleted the 'b' identifier"
+ "summary": "Deleted the 'y' identifier"
},
{
"span": {
"delete": {
"start": [
- 6,
+ 4,
13
],
"end": [
- 6,
+ 4,
14
]
}
@@ -1309,11 +1806,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
12
]
}
@@ -1324,11 +1821,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
13
],
"end": [
- 7,
+ 5,
14
]
}
@@ -1339,11 +1836,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
10
],
"end": [
- 8,
+ 6,
14
]
}
@@ -1354,11 +1851,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
15
],
"end": [
- 8,
+ 6,
20
]
}
@@ -1369,26 +1866,26 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
21
],
"end": [
- 8,
+ 6,
22
]
}
},
- "summary": "Deleted the '2'"
+ "summary": "Deleted the '1'"
},
{
"span": {
"delete": {
"start": [
- 9,
+ 7,
5
],
"end": [
- 9,
+ 7,
12
]
}
@@ -1399,11 +1896,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
13
],
"end": [
- 9,
+ 7,
14
]
}
@@ -1414,11 +1911,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
3
],
"end": [
- 10,
+ 8,
10
]
}
@@ -1429,11 +1926,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
5
],
"end": [
- 11,
+ 9,
11
]
}
@@ -1447,7 +1944,284 @@
"filePaths": [
"select-statements.go"
],
- "sha1": "9c02793fcb2f68a293f0c4f92551c34561ec4f24",
+ "patch": [
+ "diff --git a/select-statements.go b/select-statements.go",
+ "index 234dd89..d513030 100644",
+ "--- a/select-statements.go",
+ "+++ b/select-statements.go",
+ "@@ -1,14 +1,4 @@",
+ " select {",
+ "- case x := <-c:",
+ "- println(x)",
+ "- case y <- c:",
+ "- println(5)",
+ "- case <-time.After(1):",
+ "- println(6)",
+ "- default:",
+ "- return",
+ "-}",
+ "-select {",
+ " case a := <-c:",
+ " println(x)",
+ " case b <- c:"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "52c2367740c0d2f7f66fbb1638b6bbe52b8bb586"
+ "shas": "ce166d19b29200e4343c9b74fee611caf2273a62..6c726441703c87ad65a433fd78c98dd03874d274"
+}
+,{
+ "testCaseDescription": "go-select-statements-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "select-statements.go": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 8
+ ],
+ "end": [
+ 2,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 15
+ ],
+ "end": [
+ 2,
+ 16
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the 'println' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 13
+ ],
+ "end": [
+ 3,
+ 14
+ ]
+ }
+ },
+ "summary": "Deleted the 'x' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 8
+ ],
+ "end": [
+ 4,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 13
+ ],
+ "end": [
+ 4,
+ 14
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 5,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the 'println' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 13
+ ],
+ "end": [
+ 5,
+ 14
+ ]
+ }
+ },
+ "summary": "Deleted the '5'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 10
+ ],
+ "end": [
+ 6,
+ 14
+ ]
+ }
+ },
+ "summary": "Deleted the 'time' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 15
+ ],
+ "end": [
+ 6,
+ 20
+ ]
+ }
+ },
+ "summary": "Deleted the 'After' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 21
+ ],
+ "end": [
+ 6,
+ 22
+ ]
+ }
+ },
+ "summary": "Deleted the '2'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 5
+ ],
+ "end": [
+ 7,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the 'println' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 13
+ ],
+ "end": [
+ 7,
+ 14
+ ]
+ }
+ },
+ "summary": "Deleted the '6'"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 3
+ ],
+ "end": [
+ 8,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted the 'default' communication_case"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 9,
+ 5
+ ],
+ "end": [
+ 9,
+ 11
+ ]
+ }
+ },
+ "summary": "Deleted the 'empty' return statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "select-statements.go"
+ ],
+ "patch": [
+ "diff --git a/select-statements.go b/select-statements.go",
+ "index d513030..e69de29 100644",
+ "--- a/select-statements.go",
+ "+++ b/select-statements.go",
+ "@@ -1,10 +0,0 @@",
+ "-select {",
+ "- case a := <-c:",
+ "- println(x)",
+ "- case b <- c:",
+ "- println(5)",
+ "- case <-time.After(2):",
+ "- println(6)",
+ "- default:",
+ "- return",
+ "-}"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "6c726441703c87ad65a433fd78c98dd03874d274..c169e9683d54586a7fa6eab867dc6eb4eae7e85c"
}]
diff --git a/test/corpus/diff-summaries/go/selector-expressions.json b/test/corpus/diff-summaries/go/selector-expressions.json
index 754d06089..158291301 100644
--- a/test/corpus/diff-summaries/go/selector-expressions.json
+++ b/test/corpus/diff-summaries/go/selector-expressions.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
8
]
}
@@ -25,9 +25,16 @@
"filePaths": [
"selector-expressions.go"
],
- "sha1": "4f37802913bc6d0558da212b36497be55209c99b",
+ "patch": [
+ "diff --git a/selector-expressions.go b/selector-expressions.go",
+ "index e69de29..7be43f2 100644",
+ "--- a/selector-expressions.go",
+ "+++ b/selector-expressions.go",
+ "@@ -0,0 +1 @@",
+ "+a.b.c()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "41f3987a397e005336a1b76c91719e753cd5e3f4"
+ "shas": "bf82bf19d4c58176cb36d1c4e0cb934241bd5394..87d1fc7bef359bdd4e0dcc8aad67c08ce1c35f6c"
}
,{
"testCaseDescription": "go-selector-expressions-replacement-insert-test",
@@ -36,30 +43,33 @@
"selector-expressions.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'method call()' function call"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'method call()' function call"
}
]
},
@@ -68,9 +78,18 @@
"filePaths": [
"selector-expressions.go"
],
- "sha1": "41f3987a397e005336a1b76c91719e753cd5e3f4",
+ "patch": [
+ "diff --git a/selector-expressions.go b/selector-expressions.go",
+ "index 7be43f2..4fa8605 100644",
+ "--- a/selector-expressions.go",
+ "+++ b/selector-expressions.go",
+ "@@ -1 +1,3 @@",
+ "+x.y.z()",
+ "+a.b.c()",
+ " a.b.c()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "201915f3eb57c8f53b28084b3080eae7376cf15d"
+ "shas": "87d1fc7bef359bdd4e0dcc8aad67c08ce1c35f6c..ca3e3a97e47529457509431057a09ae9f09774de"
}
,{
"testCaseDescription": "go-selector-expressions-delete-insert-test",
@@ -82,21 +101,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -109,21 +128,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
},
{
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -136,21 +155,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
},
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
}
@@ -165,9 +184,19 @@
"filePaths": [
"selector-expressions.go"
],
- "sha1": "201915f3eb57c8f53b28084b3080eae7376cf15d",
+ "patch": [
+ "diff --git a/selector-expressions.go b/selector-expressions.go",
+ "index 4fa8605..2a586da 100644",
+ "--- a/selector-expressions.go",
+ "+++ b/selector-expressions.go",
+ "@@ -1,3 +1,3 @@",
+ "-x.y.z()",
+ "+a.b.c()",
+ " a.b.c()",
+ " a.b.c()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "79f050f2e282ea00bd1a5a2379c9b22ec63a216e"
+ "shas": "ca3e3a97e47529457509431057a09ae9f09774de..4784dc00012db8262fb5321370d25c7f4e2cc8d6"
}
,{
"testCaseDescription": "go-selector-expressions-replacement-test",
@@ -179,21 +208,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -206,21 +235,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
},
{
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -233,21 +262,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
},
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
}
@@ -262,9 +291,19 @@
"filePaths": [
"selector-expressions.go"
],
- "sha1": "79f050f2e282ea00bd1a5a2379c9b22ec63a216e",
+ "patch": [
+ "diff --git a/selector-expressions.go b/selector-expressions.go",
+ "index 2a586da..4fa8605 100644",
+ "--- a/selector-expressions.go",
+ "+++ b/selector-expressions.go",
+ "@@ -1,3 +1,3 @@",
+ "-a.b.c()",
+ "+x.y.z()",
+ " a.b.c()",
+ " a.b.c()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "8a2fbcba91669a62575ba3e24b843c37a3e71184"
+ "shas": "4784dc00012db8262fb5321370d25c7f4e2cc8d6..cccdb91577b7d7e692a2940325435e7129bce6a0"
}
,{
"testCaseDescription": "go-selector-expressions-delete-replacement-test",
@@ -275,11 +314,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
8
]
}
@@ -290,11 +329,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
8
]
}
@@ -305,11 +344,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
8
]
}
@@ -323,55 +362,22 @@
"filePaths": [
"selector-expressions.go"
],
- "sha1": "8a2fbcba91669a62575ba3e24b843c37a3e71184",
+ "patch": [
+ "diff --git a/selector-expressions.go b/selector-expressions.go",
+ "index 4fa8605..3e2d0bd 100644",
+ "--- a/selector-expressions.go",
+ "+++ b/selector-expressions.go",
+ "@@ -1,3 +1,2 @@",
+ "-x.y.z()",
+ "-a.b.c()",
+ " a.b.c()",
+ "+x.y.z()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "1f5ef7ae6dda1abe457f1344d1b89da8687703b9"
+ "shas": "cccdb91577b7d7e692a2940325435e7129bce6a0..a9b16a5fef8a8d18ff6629bba3baf8d652e1954a"
}
,{
"testCaseDescription": "go-selector-expressions-delete-test",
- "expectedResult": {
- "changes": {
- "selector-expressions.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- }
- ]
- },
- "summary": "Replaced the 'main' module with the 'main' module"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "selector-expressions.go"
- ],
- "sha1": "1f5ef7ae6dda1abe457f1344d1b89da8687703b9",
- "gitDir": "test/corpus/repos/go",
- "sha2": "a1ba277b8446b3a8e12bbeaa2146aaf2388971d3"
-}
-,{
- "testCaseDescription": "go-selector-expressions-delete-rest-test",
"expectedResult": {
"changes": {
"selector-expressions.go": [
@@ -379,11 +385,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
8
]
}
@@ -397,7 +403,53 @@
"filePaths": [
"selector-expressions.go"
],
- "sha1": "a1ba277b8446b3a8e12bbeaa2146aaf2388971d3",
+ "patch": [
+ "diff --git a/selector-expressions.go b/selector-expressions.go",
+ "index 3e2d0bd..00b9e7c 100644",
+ "--- a/selector-expressions.go",
+ "+++ b/selector-expressions.go",
+ "@@ -1,2 +1 @@",
+ "-a.b.c()",
+ " x.y.z()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7a0e56fcfbef48bf43e71d2d33c4b74a2cf05cb5"
+ "shas": "a9b16a5fef8a8d18ff6629bba3baf8d652e1954a..fa7f69becdee526370c1aea7e1530d2da4e1c8de"
+}
+,{
+ "testCaseDescription": "go-selector-expressions-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "selector-expressions.go": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'method call()' function call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "selector-expressions.go"
+ ],
+ "patch": [
+ "diff --git a/selector-expressions.go b/selector-expressions.go",
+ "index 00b9e7c..e69de29 100644",
+ "--- a/selector-expressions.go",
+ "+++ b/selector-expressions.go",
+ "@@ -1 +0,0 @@",
+ "-x.y.z()"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "fa7f69becdee526370c1aea7e1530d2da4e1c8de..5d7acec54aeae4a86833f9a0b00bf588083883ab"
}]
diff --git a/test/corpus/diff-summaries/go/send-statements.json b/test/corpus/diff-summaries/go/send-statements.json
index 187a2c560..92400d0f4 100644
--- a/test/corpus/diff-summaries/go/send-statements.json
+++ b/test/corpus/diff-summaries/go/send-statements.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
4
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -40,9 +40,16 @@
"filePaths": [
"send-statements.go"
],
- "sha1": "a4eb90cc8a9cbf4002ab1c646f3b965bce70cc47",
+ "patch": [
+ "diff --git a/send-statements.go b/send-statements.go",
+ "index e69de29..9df974c 100644",
+ "--- a/send-statements.go",
+ "+++ b/send-statements.go",
+ "@@ -0,0 +1 @@",
+ "+foo <- 5"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "62add87261e8579b065c88e1ebe0c4a342edc4de"
+ "shas": "1afdfc9d2ffbe4b43ec47892c4583237f382efd2..714795be33defefb56b589bf1984b5013bfd3d0f"
}
,{
"testCaseDescription": "go-send-statements-replacement-insert-test",
@@ -51,30 +58,63 @@
"send-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added 'bar' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 8
+ ],
+ "end": [
+ 1,
+ 9
+ ]
+ }
+ },
+ "summary": "Added '6'"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Added 'foo' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 8
+ ],
+ "end": [
+ 2,
+ 9
+ ]
+ }
+ },
+ "summary": "Added '5'"
}
]
},
@@ -83,9 +123,18 @@
"filePaths": [
"send-statements.go"
],
- "sha1": "62add87261e8579b065c88e1ebe0c4a342edc4de",
+ "patch": [
+ "diff --git a/send-statements.go b/send-statements.go",
+ "index 9df974c..de76cee 100644",
+ "--- a/send-statements.go",
+ "+++ b/send-statements.go",
+ "@@ -1 +1,3 @@",
+ "+bar <- 6",
+ "+foo <- 5",
+ " foo <- 5"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "34a4f845249f85d7c1dbca944865f358e54bd5aa"
+ "shas": "714795be33defefb56b589bf1984b5013bfd3d0f..d67f3c65395ec2d583d2838eb62e633160dc5bb0"
}
,{
"testCaseDescription": "go-send-statements-delete-insert-test",
@@ -97,21 +146,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
4
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
4
]
}
@@ -124,21 +173,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
},
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -153,9 +202,19 @@
"filePaths": [
"send-statements.go"
],
- "sha1": "34a4f845249f85d7c1dbca944865f358e54bd5aa",
+ "patch": [
+ "diff --git a/send-statements.go b/send-statements.go",
+ "index de76cee..d487575 100644",
+ "--- a/send-statements.go",
+ "+++ b/send-statements.go",
+ "@@ -1,3 +1,3 @@",
+ "-bar <- 6",
+ "+foo <- 5",
+ " foo <- 5",
+ " foo <- 5"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3ad99151e7a17d306cbc9188d1e972ee7eabd9f2"
+ "shas": "d67f3c65395ec2d583d2838eb62e633160dc5bb0..f3edb65315d77ba6c2c56272b231534fb537d8cc"
}
,{
"testCaseDescription": "go-send-statements-replacement-test",
@@ -167,21 +226,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
4
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
4
]
}
@@ -194,21 +253,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
},
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -223,9 +282,19 @@
"filePaths": [
"send-statements.go"
],
- "sha1": "3ad99151e7a17d306cbc9188d1e972ee7eabd9f2",
+ "patch": [
+ "diff --git a/send-statements.go b/send-statements.go",
+ "index d487575..de76cee 100644",
+ "--- a/send-statements.go",
+ "+++ b/send-statements.go",
+ "@@ -1,3 +1,3 @@",
+ "-foo <- 5",
+ "+bar <- 6",
+ " foo <- 5",
+ " foo <- 5"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "fe6d8f386756e9bf034aa26611533f41325d33e7"
+ "shas": "f3edb65315d77ba6c2c56272b231534fb537d8cc..0bab01c74332f89cf225e90aec13c47f76180a4a"
}
,{
"testCaseDescription": "go-send-statements-delete-replacement-test",
@@ -236,11 +305,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
4
]
}
@@ -251,11 +320,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -266,11 +335,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
4
]
}
@@ -281,11 +350,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
}
@@ -296,11 +365,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
4
]
}
@@ -311,11 +380,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
}
@@ -329,9 +398,19 @@
"filePaths": [
"send-statements.go"
],
- "sha1": "fe6d8f386756e9bf034aa26611533f41325d33e7",
+ "patch": [
+ "diff --git a/send-statements.go b/send-statements.go",
+ "index de76cee..65a1c23 100644",
+ "--- a/send-statements.go",
+ "+++ b/send-statements.go",
+ "@@ -1,3 +1,2 @@",
+ "-bar <- 6",
+ "-foo <- 5",
+ " foo <- 5",
+ "+bar <- 6"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "27a0815cc703e9ca882601641e3ff5106b08f1b3"
+ "shas": "0bab01c74332f89cf225e90aec13c47f76180a4a..659323e1c3b72c8aeb375fe6afca8af9afd91380"
}
,{
"testCaseDescription": "go-send-statements-delete-test",
@@ -340,30 +419,33 @@
"send-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
},
- "summary": "Replaced 'main' module with 'main' module"
+ "summary": "Deleted 'foo' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 8
+ ],
+ "end": [
+ 1,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted '5'"
}
]
},
@@ -372,9 +454,17 @@
"filePaths": [
"send-statements.go"
],
- "sha1": "27a0815cc703e9ca882601641e3ff5106b08f1b3",
+ "patch": [
+ "diff --git a/send-statements.go b/send-statements.go",
+ "index 65a1c23..bab29cb 100644",
+ "--- a/send-statements.go",
+ "+++ b/send-statements.go",
+ "@@ -1,2 +1 @@",
+ "-foo <- 5",
+ " bar <- 6"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f49d172b1fdce66fae95c6d73f01dd5f27a9a5d8"
+ "shas": "659323e1c3b72c8aeb375fe6afca8af9afd91380..659afeebaae01516ea3532538f0ea665e2823020"
}
,{
"testCaseDescription": "go-send-statements-delete-rest-test",
@@ -385,11 +475,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
4
]
}
@@ -400,11 +490,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -418,7 +508,14 @@
"filePaths": [
"send-statements.go"
],
- "sha1": "f49d172b1fdce66fae95c6d73f01dd5f27a9a5d8",
+ "patch": [
+ "diff --git a/send-statements.go b/send-statements.go",
+ "index bab29cb..e69de29 100644",
+ "--- a/send-statements.go",
+ "+++ b/send-statements.go",
+ "@@ -1 +0,0 @@",
+ "-bar <- 6"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "353e531a55c6c3d0540570c523e799df46615898"
+ "shas": "659afeebaae01516ea3532538f0ea665e2823020..acf23921d6e89772dac98a78ba280e58c2429050"
}]
diff --git a/test/corpus/diff-summaries/go/short-var-declarations.json b/test/corpus/diff-summaries/go/short-var-declarations.json
index 21b17820e..ce93175cd 100644
--- a/test/corpus/diff-summaries/go/short-var-declarations.json
+++ b/test/corpus/diff-summaries/go/short-var-declarations.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -40,9 +40,16 @@
"filePaths": [
"short-var-declarations.go"
],
- "sha1": "c960fcc65ac55182c76b10f2b295a3cc10166860",
+ "patch": [
+ "diff --git a/short-var-declarations.go b/short-var-declarations.go",
+ "index e69de29..99b7041 100644",
+ "--- a/short-var-declarations.go",
+ "+++ b/short-var-declarations.go",
+ "@@ -0,0 +1 @@",
+ "+a, b := 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "1a783799a30336dc4b9798aef977bb2a4ad30d5d"
+ "shas": "294f5cc0ef0e25ecf0309fd41ae6cd4b376ab627..7ec7132712c0483a2acf6807c9e0b400580acf30"
}
,{
"testCaseDescription": "go-short-var-declarations-replacement-insert-test",
@@ -51,30 +58,63 @@
"short-var-declarations.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 13
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'x' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the 'y' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the 'a' variable"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the 'b' variable"
}
]
},
@@ -83,9 +123,18 @@
"filePaths": [
"short-var-declarations.go"
],
- "sha1": "1a783799a30336dc4b9798aef977bb2a4ad30d5d",
+ "patch": [
+ "diff --git a/short-var-declarations.go b/short-var-declarations.go",
+ "index 99b7041..220aab8 100644",
+ "--- a/short-var-declarations.go",
+ "+++ b/short-var-declarations.go",
+ "@@ -1 +1,3 @@",
+ "+x, y := 3, 4",
+ "+a, b := 1, 2",
+ " a, b := 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "950d07065887bd080775b0257f250b3b53f35d53"
+ "shas": "7ec7132712c0483a2acf6807c9e0b400580acf30..d55246a1bf4a17fe28258dccf542d3a6ebaf922a"
}
,{
"testCaseDescription": "go-short-var-declarations-delete-insert-test",
@@ -97,21 +146,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -124,21 +173,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
},
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -151,21 +200,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
},
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -178,21 +227,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
13
]
},
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
13
]
}
@@ -207,9 +256,19 @@
"filePaths": [
"short-var-declarations.go"
],
- "sha1": "950d07065887bd080775b0257f250b3b53f35d53",
+ "patch": [
+ "diff --git a/short-var-declarations.go b/short-var-declarations.go",
+ "index 220aab8..96ba966 100644",
+ "--- a/short-var-declarations.go",
+ "+++ b/short-var-declarations.go",
+ "@@ -1,3 +1,3 @@",
+ "-x, y := 3, 4",
+ "+a, b := 1, 2",
+ " a, b := 1, 2",
+ " a, b := 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "2e165e3a8349e288cf5df008c91215a6d1e0eea1"
+ "shas": "d55246a1bf4a17fe28258dccf542d3a6ebaf922a..8984549fa93dd35873e2ee52afc2af3f04791d1c"
}
,{
"testCaseDescription": "go-short-var-declarations-replacement-test",
@@ -221,21 +280,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -248,21 +307,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
},
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -275,21 +334,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
},
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -302,21 +361,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
13
]
},
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
13
]
}
@@ -331,9 +390,19 @@
"filePaths": [
"short-var-declarations.go"
],
- "sha1": "2e165e3a8349e288cf5df008c91215a6d1e0eea1",
+ "patch": [
+ "diff --git a/short-var-declarations.go b/short-var-declarations.go",
+ "index 96ba966..220aab8 100644",
+ "--- a/short-var-declarations.go",
+ "+++ b/short-var-declarations.go",
+ "@@ -1,3 +1,3 @@",
+ "-a, b := 1, 2",
+ "+x, y := 3, 4",
+ " a, b := 1, 2",
+ " a, b := 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f824e878031e2b1d44d93528ba9c60b4cef6083d"
+ "shas": "8984549fa93dd35873e2ee52afc2af3f04791d1c..dd109e24c6a2d3b52a0e1579fa93be09e86bfbbb"
}
,{
"testCaseDescription": "go-short-var-declarations-delete-replacement-test",
@@ -344,11 +413,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -359,11 +428,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -374,11 +443,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
13
]
}
@@ -389,11 +458,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
13
]
}
@@ -404,11 +473,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
13
]
}
@@ -419,11 +488,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
13
]
}
@@ -437,9 +506,19 @@
"filePaths": [
"short-var-declarations.go"
],
- "sha1": "f824e878031e2b1d44d93528ba9c60b4cef6083d",
+ "patch": [
+ "diff --git a/short-var-declarations.go b/short-var-declarations.go",
+ "index 220aab8..53cb4ed 100644",
+ "--- a/short-var-declarations.go",
+ "+++ b/short-var-declarations.go",
+ "@@ -1,3 +1,2 @@",
+ "-x, y := 3, 4",
+ "-a, b := 1, 2",
+ " a, b := 1, 2",
+ "+x, y := 3, 4"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "32c2030e4597ceafbb01ff6e3d6189c4c0c1df4d"
+ "shas": "dd109e24c6a2d3b52a0e1579fa93be09e86bfbbb..068c4c6e6ce030231dcd6b1f5ae3d282a4f6ba47"
}
,{
"testCaseDescription": "go-short-var-declarations-delete-test",
@@ -448,30 +527,33 @@
"short-var-declarations.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 13
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'a' variable"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' variable"
}
]
},
@@ -480,9 +562,17 @@
"filePaths": [
"short-var-declarations.go"
],
- "sha1": "32c2030e4597ceafbb01ff6e3d6189c4c0c1df4d",
+ "patch": [
+ "diff --git a/short-var-declarations.go b/short-var-declarations.go",
+ "index 53cb4ed..9209ec7 100644",
+ "--- a/short-var-declarations.go",
+ "+++ b/short-var-declarations.go",
+ "@@ -1,2 +1 @@",
+ "-a, b := 1, 2",
+ " x, y := 3, 4"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "86e943ef7847ca3016b391c44cb7fdee78d9d927"
+ "shas": "068c4c6e6ce030231dcd6b1f5ae3d282a4f6ba47..5a9292f0154404769494bed8797a68db3bf662ad"
}
,{
"testCaseDescription": "go-short-var-declarations-delete-rest-test",
@@ -493,11 +583,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -508,11 +598,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -526,7 +616,14 @@
"filePaths": [
"short-var-declarations.go"
],
- "sha1": "86e943ef7847ca3016b391c44cb7fdee78d9d927",
+ "patch": [
+ "diff --git a/short-var-declarations.go b/short-var-declarations.go",
+ "index 9209ec7..e69de29 100644",
+ "--- a/short-var-declarations.go",
+ "+++ b/short-var-declarations.go",
+ "@@ -1 +0,0 @@",
+ "-x, y := 3, 4"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b553e5d63655ec620ade647a1f3551dfa59d2277"
+ "shas": "5a9292f0154404769494bed8797a68db3bf662ad..aa129cc05ef2a77358a80e1404c396003e3738af"
}]
diff --git a/test/corpus/diff-summaries/go/single-import-declarations.json b/test/corpus/diff-summaries/go/single-import-declarations.json
index 5411b9009..17356ab1f 100644
--- a/test/corpus/diff-summaries/go/single-import-declarations.json
+++ b/test/corpus/diff-summaries/go/single-import-declarations.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
18
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
20
]
}
@@ -41,16 +41,16 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
28
]
}
},
- "summary": "Added the 'import alias \"some/package\"' at line 5, column 1 - line 5, column 28"
+ "summary": "Added the 'import alias \"some/package\"' at line 3, column 1 - line 3, column 28"
}
]
}
@@ -58,9 +58,18 @@
"filePaths": [
"single-import-declarations.go"
],
- "sha1": "489adde209f940544e660d374c47bbc860b9c72b",
+ "patch": [
+ "diff --git a/single-import-declarations.go b/single-import-declarations.go",
+ "index e69de29..e30eddb 100644",
+ "--- a/single-import-declarations.go",
+ "+++ b/single-import-declarations.go",
+ "@@ -0,0 +1,3 @@",
+ "+import \"net/http\"",
+ "+import . \"some/dsl\"",
+ "+import alias \"some/package\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a6757a56251ba2d618305d1b2ae2fd719f8a3e28"
+ "shas": "b755f1d4404210b76f3d304569455d98b90fa186..437e7db7a8729ba8a685986dd98343129eaf289b"
}
,{
"testCaseDescription": "go-single-import-declarations-replacement-insert-test",
@@ -71,11 +80,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
17
]
}
@@ -86,11 +95,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
21
]
}
@@ -101,11 +110,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
18
]
}
@@ -116,11 +125,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
20
]
}
@@ -135,31 +144,31 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
32
]
}
},
- "summary": "Added the 'import alias \"awesome/packages\"' at line 5, column 1 - line 5, column 32"
+ "summary": "Added the 'import alias \"awesome/packages\"' at line 3, column 1 - line 3, column 32"
},
{
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
28
]
}
},
- "summary": "Added the 'import alias \"some/package\"' at line 8, column 1 - line 8, column 28"
+ "summary": "Added the 'import alias \"some/package\"' at line 6, column 1 - line 6, column 28"
}
]
}
@@ -167,9 +176,24 @@
"filePaths": [
"single-import-declarations.go"
],
- "sha1": "a6757a56251ba2d618305d1b2ae2fd719f8a3e28",
+ "patch": [
+ "diff --git a/single-import-declarations.go b/single-import-declarations.go",
+ "index e30eddb..a6141af 100644",
+ "--- a/single-import-declarations.go",
+ "+++ b/single-import-declarations.go",
+ "@@ -1,3 +1,9 @@",
+ "+import \"foo/bar\"",
+ "+import . \"types/dsl\"",
+ "+import alias \"awesome/packages\"",
+ "+import \"net/http\"",
+ "+import . \"some/dsl\"",
+ "+import alias \"some/package\"",
+ " import \"net/http\"",
+ " import . \"some/dsl\"",
+ " import alias \"some/package\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "960ff51ff3afe7ef94a8ca0f7eca90a7187f81bd"
+ "shas": "437e7db7a8729ba8a685986dd98343129eaf289b..24c2801f35fbac08fe710af7d34a6de746be8b8d"
}
,{
"testCaseDescription": "go-single-import-declarations-delete-insert-test",
@@ -181,75 +205,75 @@
"replace": [
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
17
]
},
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
18
]
}
]
},
- "summary": "Replaced the \"foo/bar\" string with the \"net/http\" string in the \"net/http\" import statement of the 'main' module"
+ "summary": "Replaced the \"foo/bar\" string with the \"net/http\" string in the \"net/http\" import statement"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
21
]
},
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
20
]
}
]
},
- "summary": "Replaced the \"types/dsl\" string with the \"some/dsl\" string in the \"some/dsl\" import statement of the 'main' module"
+ "summary": "Replaced the \"types/dsl\" string with the \"some/dsl\" string in the \"some/dsl\" import statement"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
14
],
"end": [
- 5,
+ 3,
32
]
},
{
"start": [
- 5,
+ 3,
14
],
"end": [
- 5,
+ 3,
28
]
}
@@ -264,9 +288,24 @@
"filePaths": [
"single-import-declarations.go"
],
- "sha1": "960ff51ff3afe7ef94a8ca0f7eca90a7187f81bd",
+ "patch": [
+ "diff --git a/single-import-declarations.go b/single-import-declarations.go",
+ "index a6141af..b54ad96 100644",
+ "--- a/single-import-declarations.go",
+ "+++ b/single-import-declarations.go",
+ "@@ -1,6 +1,6 @@",
+ "-import \"foo/bar\"",
+ "-import . \"types/dsl\"",
+ "-import alias \"awesome/packages\"",
+ "+import \"net/http\"",
+ "+import . \"some/dsl\"",
+ "+import alias \"some/package\"",
+ " import \"net/http\"",
+ " import . \"some/dsl\"",
+ " import alias \"some/package\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "5e23bd9f1d9ccbde466105805444a19d662a2281"
+ "shas": "24c2801f35fbac08fe710af7d34a6de746be8b8d..330336208dc9988acdd03b84111ed42f47a68cc1"
}
,{
"testCaseDescription": "go-single-import-declarations-replacement-test",
@@ -278,75 +317,75 @@
"replace": [
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
18
]
},
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
17
]
}
]
},
- "summary": "Replaced the \"net/http\" string with the \"foo/bar\" string in the \"foo/bar\" import statement of the 'main' module"
+ "summary": "Replaced the \"net/http\" string with the \"foo/bar\" string in the \"foo/bar\" import statement"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
20
]
},
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
21
]
}
]
},
- "summary": "Replaced the \"some/dsl\" string with the \"types/dsl\" string in the \"types/dsl\" import statement of the 'main' module"
+ "summary": "Replaced the \"some/dsl\" string with the \"types/dsl\" string in the \"types/dsl\" import statement"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
14
],
"end": [
- 5,
+ 3,
28
]
},
{
"start": [
- 5,
+ 3,
14
],
"end": [
- 5,
+ 3,
32
]
}
@@ -361,9 +400,24 @@
"filePaths": [
"single-import-declarations.go"
],
- "sha1": "5e23bd9f1d9ccbde466105805444a19d662a2281",
+ "patch": [
+ "diff --git a/single-import-declarations.go b/single-import-declarations.go",
+ "index b54ad96..a6141af 100644",
+ "--- a/single-import-declarations.go",
+ "+++ b/single-import-declarations.go",
+ "@@ -1,6 +1,6 @@",
+ "-import \"net/http\"",
+ "-import . \"some/dsl\"",
+ "-import alias \"some/package\"",
+ "+import \"foo/bar\"",
+ "+import . \"types/dsl\"",
+ "+import alias \"awesome/packages\"",
+ " import \"net/http\"",
+ " import . \"some/dsl\"",
+ " import alias \"some/package\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3a34d3922437ed1c541317cec4d6d0832a7c73c1"
+ "shas": "330336208dc9988acdd03b84111ed42f47a68cc1..fed29600ad272abe4d05fb7b4bb406a408ef62d9"
}
,{
"testCaseDescription": "go-single-import-declarations-delete-replacement-test",
@@ -374,11 +428,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
17
]
}
@@ -389,11 +443,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
21
]
}
@@ -404,11 +458,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
18
]
}
@@ -419,11 +473,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
20
]
}
@@ -434,11 +488,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
17
]
}
@@ -449,11 +503,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
21
]
}
@@ -468,46 +522,46 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
32
]
}
},
- "summary": "Deleted the 'import alias \"awesome/packages\"' at line 5, column 1 - line 5, column 32"
+ "summary": "Deleted the 'import alias \"awesome/packages\"' at line 3, column 1 - line 3, column 32"
},
{
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
28
]
}
},
- "summary": "Deleted the 'import alias \"some/package\"' at line 8, column 1 - line 8, column 28"
+ "summary": "Deleted the 'import alias \"some/package\"' at line 6, column 1 - line 6, column 28"
},
{
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
32
]
}
},
- "summary": "Added the 'import alias \"awesome/packages\"' at line 8, column 1 - line 8, column 32"
+ "summary": "Added the 'import alias \"awesome/packages\"' at line 6, column 1 - line 6, column 32"
}
]
}
@@ -515,9 +569,27 @@
"filePaths": [
"single-import-declarations.go"
],
- "sha1": "3a34d3922437ed1c541317cec4d6d0832a7c73c1",
+ "patch": [
+ "diff --git a/single-import-declarations.go b/single-import-declarations.go",
+ "index a6141af..98c2392 100644",
+ "--- a/single-import-declarations.go",
+ "+++ b/single-import-declarations.go",
+ "@@ -1,9 +1,6 @@",
+ "-import \"foo/bar\"",
+ "-import . \"types/dsl\"",
+ "-import alias \"awesome/packages\"",
+ "-import \"net/http\"",
+ "-import . \"some/dsl\"",
+ "-import alias \"some/package\"",
+ " import \"net/http\"",
+ " import . \"some/dsl\"",
+ " import alias \"some/package\"",
+ "+import \"foo/bar\"",
+ "+import . \"types/dsl\"",
+ "+import alias \"awesome/packages\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c8c900b5aafe5f4f1cefb69838267401815cf0cd"
+ "shas": "fed29600ad272abe4d05fb7b4bb406a408ef62d9..d8fe5f813263407b360696c773393622f8626ac8"
}
,{
"testCaseDescription": "go-single-import-declarations-delete-test",
@@ -528,11 +600,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
18
]
}
@@ -543,11 +615,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
20
]
}
@@ -562,16 +634,16 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
28
]
}
},
- "summary": "Deleted the 'import alias \"some/package\"' at line 5, column 1 - line 5, column 28"
+ "summary": "Deleted the 'import alias \"some/package\"' at line 3, column 1 - line 3, column 28"
}
]
}
@@ -579,9 +651,21 @@
"filePaths": [
"single-import-declarations.go"
],
- "sha1": "c8c900b5aafe5f4f1cefb69838267401815cf0cd",
+ "patch": [
+ "diff --git a/single-import-declarations.go b/single-import-declarations.go",
+ "index 98c2392..8af8c6d 100644",
+ "--- a/single-import-declarations.go",
+ "+++ b/single-import-declarations.go",
+ "@@ -1,6 +1,3 @@",
+ "-import \"net/http\"",
+ "-import . \"some/dsl\"",
+ "-import alias \"some/package\"",
+ " import \"foo/bar\"",
+ " import . \"types/dsl\"",
+ " import alias \"awesome/packages\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "645d50be110772c29dd4a1c2e842bbf06aa43569"
+ "shas": "d8fe5f813263407b360696c773393622f8626ac8..a322dc7bac3a14fa7b2bc7584e05add891842d38"
}
,{
"testCaseDescription": "go-single-import-declarations-delete-rest-test",
@@ -592,11 +676,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
17
]
}
@@ -607,11 +691,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
21
]
}
@@ -626,16 +710,16 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
32
]
}
},
- "summary": "Deleted the 'import alias \"awesome/packages\"' at line 5, column 1 - line 5, column 32"
+ "summary": "Deleted the 'import alias \"awesome/packages\"' at line 3, column 1 - line 3, column 32"
}
]
}
@@ -643,7 +727,16 @@
"filePaths": [
"single-import-declarations.go"
],
- "sha1": "645d50be110772c29dd4a1c2e842bbf06aa43569",
+ "patch": [
+ "diff --git a/single-import-declarations.go b/single-import-declarations.go",
+ "index 8af8c6d..e69de29 100644",
+ "--- a/single-import-declarations.go",
+ "+++ b/single-import-declarations.go",
+ "@@ -1,3 +0,0 @@",
+ "-import \"foo/bar\"",
+ "-import . \"types/dsl\"",
+ "-import alias \"awesome/packages\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "60d0595870f22587e7f31bed659faaa89e73c81d"
+ "shas": "a322dc7bac3a14fa7b2bc7584e05add891842d38..49405e780f45c25871a6c2c6a9c4bf847007c59f"
}]
diff --git a/test/corpus/diff-summaries/go/single-line-function-declarations.json b/test/corpus/diff-summaries/go/single-line-function-declarations.json
index 14304ef19..3c5e74b1f 100644
--- a/test/corpus/diff-summaries/go/single-line-function-declarations.json
+++ b/test/corpus/diff-summaries/go/single-line-function-declarations.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
18
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
23
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
24
]
}
@@ -55,9 +55,18 @@
"filePaths": [
"single-line-function-declarations.go"
],
- "sha1": "3859e3f291b6fe933be02dbc730935422b0aafb0",
+ "patch": [
+ "diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
+ "index e69de29..3ac1720 100644",
+ "--- a/single-line-function-declarations.go",
+ "+++ b/single-line-function-declarations.go",
+ "@@ -0,0 +1,3 @@",
+ "+func f1() { a() }",
+ "+func f2() { a(); b() }",
+ "+func f3() { a(); b(); }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "05e1472680c28fa54012fee5a06f0f7a0e5912a9"
+ "shas": "9096649c53a965576d44aa8d1b52f7b63d420fea..cae2b3de861d0266a7437eed7937500a50a26873"
}
,{
"testCaseDescription": "go-single-line-function-declarations-replacement-insert-test",
@@ -68,11 +77,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
18
]
}
@@ -83,11 +92,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
23
]
}
@@ -98,11 +107,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
24
]
}
@@ -113,11 +122,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
18
]
}
@@ -128,11 +137,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
23
]
}
@@ -143,11 +152,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
24
]
}
@@ -161,9 +170,24 @@
"filePaths": [
"single-line-function-declarations.go"
],
- "sha1": "05e1472680c28fa54012fee5a06f0f7a0e5912a9",
+ "patch": [
+ "diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
+ "index 3ac1720..39e0696 100644",
+ "--- a/single-line-function-declarations.go",
+ "+++ b/single-line-function-declarations.go",
+ "@@ -1,3 +1,9 @@",
+ "+func g1() { a() }",
+ "+func g2() { a(); b() }",
+ "+func g3() { a(); b(); }",
+ "+func f1() { a() }",
+ "+func f2() { a(); b() }",
+ "+func f3() { a(); b(); }",
+ " func f1() { a() }",
+ " func f2() { a(); b() }",
+ " func f3() { a(); b(); }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3019b504597b211e81deb8d9c25d0b866d70e87d"
+ "shas": "cae2b3de861d0266a7437eed7937500a50a26873..48dfe25b8ab21ce6cc4d3b1d2047b474fe1cc13b"
}
,{
"testCaseDescription": "go-single-line-function-declarations-delete-insert-test",
@@ -175,81 +199,81 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
]
},
- "summary": "Replaced the 'g1' identifier with the 'f1' identifier in the f1 function of the 'main' module"
+ "summary": "Replaced the 'g1' identifier with the 'f1' identifier in the f1 function"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
]
},
- "summary": "Replaced the 'g2' identifier with the 'f2' identifier in the f2 function of the 'main' module"
+ "summary": "Replaced the 'g2' identifier with the 'f2' identifier in the f2 function"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
]
},
- "summary": "Replaced the 'g3' identifier with the 'f3' identifier in the f3 function of the 'main' module"
+ "summary": "Replaced the 'g3' identifier with the 'f3' identifier in the f3 function"
}
]
},
@@ -258,9 +282,24 @@
"filePaths": [
"single-line-function-declarations.go"
],
- "sha1": "3019b504597b211e81deb8d9c25d0b866d70e87d",
+ "patch": [
+ "diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
+ "index 39e0696..eec54a8 100644",
+ "--- a/single-line-function-declarations.go",
+ "+++ b/single-line-function-declarations.go",
+ "@@ -1,6 +1,6 @@",
+ "-func g1() { a() }",
+ "-func g2() { a(); b() }",
+ "-func g3() { a(); b(); }",
+ "+func f1() { a() }",
+ "+func f2() { a(); b() }",
+ "+func f3() { a(); b(); }",
+ " func f1() { a() }",
+ " func f2() { a(); b() }",
+ " func f3() { a(); b(); }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "bd945223a19928035a820b953198e3ce94590248"
+ "shas": "48dfe25b8ab21ce6cc4d3b1d2047b474fe1cc13b..3741e0652eb253b416b04872a63d816ccc25d1a6"
}
,{
"testCaseDescription": "go-single-line-function-declarations-replacement-test",
@@ -272,81 +311,81 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
]
},
- "summary": "Replaced the 'f1' identifier with the 'g1' identifier in the g1 function of the 'main' module"
+ "summary": "Replaced the 'f1' identifier with the 'g1' identifier in the g1 function"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
]
},
- "summary": "Replaced the 'f2' identifier with the 'g2' identifier in the g2 function of the 'main' module"
+ "summary": "Replaced the 'f2' identifier with the 'g2' identifier in the g2 function"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
]
},
- "summary": "Replaced the 'f3' identifier with the 'g3' identifier in the g3 function of the 'main' module"
+ "summary": "Replaced the 'f3' identifier with the 'g3' identifier in the g3 function"
}
]
},
@@ -355,9 +394,24 @@
"filePaths": [
"single-line-function-declarations.go"
],
- "sha1": "bd945223a19928035a820b953198e3ce94590248",
+ "patch": [
+ "diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
+ "index eec54a8..39e0696 100644",
+ "--- a/single-line-function-declarations.go",
+ "+++ b/single-line-function-declarations.go",
+ "@@ -1,6 +1,6 @@",
+ "-func f1() { a() }",
+ "-func f2() { a(); b() }",
+ "-func f3() { a(); b(); }",
+ "+func g1() { a() }",
+ "+func g2() { a(); b() }",
+ "+func g3() { a(); b(); }",
+ " func f1() { a() }",
+ " func f2() { a(); b() }",
+ " func f3() { a(); b(); }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "d1fe7332442f0732a82dc41756a860a784461a01"
+ "shas": "3741e0652eb253b416b04872a63d816ccc25d1a6..d8b23ec7c0f30bb603eda112e423f35c5d53d1b1"
}
,{
"testCaseDescription": "go-single-line-function-declarations-delete-replacement-test",
@@ -368,11 +422,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
18
]
}
@@ -383,11 +437,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
23
]
}
@@ -398,11 +452,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
24
]
}
@@ -413,11 +467,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
18
]
}
@@ -428,11 +482,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
23
]
}
@@ -443,11 +497,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
24
]
}
@@ -458,11 +512,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
18
]
}
@@ -473,11 +527,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
23
]
}
@@ -488,11 +542,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
24
]
}
@@ -506,9 +560,27 @@
"filePaths": [
"single-line-function-declarations.go"
],
- "sha1": "d1fe7332442f0732a82dc41756a860a784461a01",
+ "patch": [
+ "diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
+ "index 39e0696..7fcb3a1 100644",
+ "--- a/single-line-function-declarations.go",
+ "+++ b/single-line-function-declarations.go",
+ "@@ -1,9 +1,6 @@",
+ "-func g1() { a() }",
+ "-func g2() { a(); b() }",
+ "-func g3() { a(); b(); }",
+ "-func f1() { a() }",
+ "-func f2() { a(); b() }",
+ "-func f3() { a(); b(); }",
+ " func f1() { a() }",
+ " func f2() { a(); b() }",
+ " func f3() { a(); b(); }",
+ "+func g1() { a() }",
+ "+func g2() { a(); b() }",
+ "+func g3() { a(); b(); }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "76cdb2d4f70ba087e9d75bf3e04d668a343d1d41"
+ "shas": "d8b23ec7c0f30bb603eda112e423f35c5d53d1b1..20c4ef7df079d3437ea04953c1c5312cb54f1002"
}
,{
"testCaseDescription": "go-single-line-function-declarations-delete-test",
@@ -519,11 +591,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
18
]
}
@@ -534,11 +606,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
23
]
}
@@ -549,11 +621,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
24
]
}
@@ -567,9 +639,21 @@
"filePaths": [
"single-line-function-declarations.go"
],
- "sha1": "76cdb2d4f70ba087e9d75bf3e04d668a343d1d41",
+ "patch": [
+ "diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
+ "index 7fcb3a1..ef4196f 100644",
+ "--- a/single-line-function-declarations.go",
+ "+++ b/single-line-function-declarations.go",
+ "@@ -1,6 +1,3 @@",
+ "-func f1() { a() }",
+ "-func f2() { a(); b() }",
+ "-func f3() { a(); b(); }",
+ " func g1() { a() }",
+ " func g2() { a(); b() }",
+ " func g3() { a(); b(); }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "155eee8f053d32a704ba6bc1502e2e2b828b81cb"
+ "shas": "20c4ef7df079d3437ea04953c1c5312cb54f1002..ad3299189246bfc5df44d7866c05fd40ccd34abc"
}
,{
"testCaseDescription": "go-single-line-function-declarations-delete-rest-test",
@@ -580,11 +664,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
18
]
}
@@ -595,11 +679,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
23
]
}
@@ -610,11 +694,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
24
]
}
@@ -628,7 +712,16 @@
"filePaths": [
"single-line-function-declarations.go"
],
- "sha1": "155eee8f053d32a704ba6bc1502e2e2b828b81cb",
+ "patch": [
+ "diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
+ "index ef4196f..e69de29 100644",
+ "--- a/single-line-function-declarations.go",
+ "+++ b/single-line-function-declarations.go",
+ "@@ -1,3 +0,0 @@",
+ "-func g1() { a() }",
+ "-func g2() { a(); b() }",
+ "-func g3() { a(); b(); }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "1011eae016159133bb9b3305fa29900aa6f06827"
+ "shas": "ad3299189246bfc5df44d7866c05fd40ccd34abc..256c131008b104fa15d57c0f3ff56131c11337fe"
}]
diff --git a/test/corpus/diff-summaries/go/slice-literals.json b/test/corpus/diff-summaries/go/slice-literals.json
index bce5a8810..2d5432ee2 100644
--- a/test/corpus/diff-summaries/go/slice-literals.json
+++ b/test/corpus/diff-summaries/go/slice-literals.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
26
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -55,9 +55,21 @@
"filePaths": [
"slice-literals.go"
],
- "sha1": "e727d68d5530b584f126dc2c23f5dafc2ed9f862",
+ "patch": [
+ "diff --git a/slice-literals.go b/slice-literals.go",
+ "index e69de29..9b1eb7a 100644",
+ "--- a/slice-literals.go",
+ "+++ b/slice-literals.go",
+ "@@ -0,0 +1,6 @@",
+ "+const s1 = []string{}",
+ "+const s2 = []string{\"hi\"}",
+ "+const s3 = []string{",
+ "+\"hi\",",
+ "+ \"hello\",",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7d1dc33757ba083fa8c0a4ee6420a19ba409a632"
+ "shas": "9e795da07ee62f0a45cb22c279f0ac4a7f3d43d7..7e5f16141af567d499956917afac82cf54db902b"
}
,{
"testCaseDescription": "go-slice-literals-replacement-insert-test",
@@ -68,11 +80,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
27
]
}
@@ -83,11 +95,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
29
]
}
@@ -98,11 +110,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -113,11 +125,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
22
]
}
@@ -128,11 +140,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
1
],
"end": [
- 10,
+ 8,
26
]
}
@@ -143,11 +155,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 14,
+ 12,
2
]
}
@@ -161,9 +173,30 @@
"filePaths": [
"slice-literals.go"
],
- "sha1": "7d1dc33757ba083fa8c0a4ee6420a19ba409a632",
+ "patch": [
+ "diff --git a/slice-literals.go b/slice-literals.go",
+ "index 9b1eb7a..4555163 100644",
+ "--- a/slice-literals.go",
+ "+++ b/slice-literals.go",
+ "@@ -1,3 +1,15 @@",
+ "+const s1 = []string{\"sup\"}",
+ "+const s2 = []string{\"hello\"}",
+ "+const s3 = []string{",
+ "+\"bar\",",
+ "+ \"baz\",",
+ "+}",
+ "+const s1 = []string{}",
+ "+const s2 = []string{\"hi\"}",
+ "+const s3 = []string{",
+ "+\"hi\",",
+ "+ \"hello\",",
+ "+}",
+ " const s1 = []string{}",
+ " const s2 = []string{\"hi\"}",
+ " const s3 = []string{"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "2777faca7f750c059198d05cdeb7506db55f5b44"
+ "shas": "7e5f16141af567d499956917afac82cf54db902b..430df208c0280d2df11bed2f3f13ef4d0b0ad9fc"
}
,{
"testCaseDescription": "go-slice-literals-delete-insert-test",
@@ -175,108 +208,108 @@
"replace": [
{
"start": [
- 3,
+ 1,
21
],
"end": [
- 3,
+ 1,
26
]
},
{
"start": [
- 3,
+ 1,
20
],
"end": [
- 3,
+ 1,
22
]
}
]
},
- "summary": "Replaced the \"sup\" string with the '{}' literal_value in the s1 variable of the 'main' module"
+ "summary": "Replaced the \"sup\" string with the '{}' literal_value in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
21
],
"end": [
- 4,
+ 2,
28
]
},
{
"start": [
- 4,
+ 2,
21
],
"end": [
- 4,
+ 2,
25
]
}
]
},
- "summary": "Replaced the \"hello\" string with the \"hi\" string in the s2 variable of the 'main' module"
+ "summary": "Replaced the \"hello\" string with the \"hi\" string in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
6
]
},
{
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
5
]
}
]
},
- "summary": "Replaced the \"bar\" string with the \"hi\" string in the s3 variable of the 'main' module"
+ "summary": "Replaced the \"bar\" string with the \"hi\" string in the s3 variable"
},
{
"span": {
"replace": [
{
"start": [
- 7,
+ 5,
2
],
"end": [
- 7,
+ 5,
7
]
},
{
"start": [
- 7,
+ 5,
2
],
"end": [
- 7,
+ 5,
9
]
}
]
},
- "summary": "Replaced the \"baz\" string with the \"hello\" string in the s3 variable of the 'main' module"
+ "summary": "Replaced the \"baz\" string with the \"hello\" string in the s3 variable"
}
]
},
@@ -285,9 +318,27 @@
"filePaths": [
"slice-literals.go"
],
- "sha1": "2777faca7f750c059198d05cdeb7506db55f5b44",
+ "patch": [
+ "diff --git a/slice-literals.go b/slice-literals.go",
+ "index 4555163..39a2067 100644",
+ "--- a/slice-literals.go",
+ "+++ b/slice-literals.go",
+ "@@ -1,8 +1,8 @@",
+ "-const s1 = []string{\"sup\"}",
+ "-const s2 = []string{\"hello\"}",
+ "+const s1 = []string{}",
+ "+const s2 = []string{\"hi\"}",
+ " const s3 = []string{",
+ "-\"bar\",",
+ "- \"baz\",",
+ "+\"hi\",",
+ "+ \"hello\",",
+ " }",
+ " const s1 = []string{}",
+ " const s2 = []string{\"hi\"}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "6c12749cd08a72bbdef593a7c7a81b9d863afb10"
+ "shas": "430df208c0280d2df11bed2f3f13ef4d0b0ad9fc..6d5b83fd5bcf434b3dc818de211b89abee2d6cf4"
}
,{
"testCaseDescription": "go-slice-literals-replacement-test",
@@ -299,108 +350,108 @@
"replace": [
{
"start": [
- 3,
+ 1,
20
],
"end": [
- 3,
+ 1,
22
]
},
{
"start": [
- 3,
+ 1,
21
],
"end": [
- 3,
+ 1,
26
]
}
]
},
- "summary": "Replaced the '{}' literal_value with the \"sup\" string in the s1 variable of the 'main' module"
+ "summary": "Replaced the '{}' literal_value with the \"sup\" string in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
21
],
"end": [
- 4,
+ 2,
25
]
},
{
"start": [
- 4,
+ 2,
21
],
"end": [
- 4,
+ 2,
28
]
}
]
},
- "summary": "Replaced the \"hi\" string with the \"hello\" string in the s2 variable of the 'main' module"
+ "summary": "Replaced the \"hi\" string with the \"hello\" string in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
5
]
},
{
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
6
]
}
]
},
- "summary": "Replaced the \"hi\" string with the \"bar\" string in the s3 variable of the 'main' module"
+ "summary": "Replaced the \"hi\" string with the \"bar\" string in the s3 variable"
},
{
"span": {
"replace": [
{
"start": [
- 7,
+ 5,
2
],
"end": [
- 7,
+ 5,
9
]
},
{
"start": [
- 7,
+ 5,
2
],
"end": [
- 7,
+ 5,
7
]
}
]
},
- "summary": "Replaced the \"hello\" string with the \"baz\" string in the s3 variable of the 'main' module"
+ "summary": "Replaced the \"hello\" string with the \"baz\" string in the s3 variable"
}
]
},
@@ -409,9 +460,27 @@
"filePaths": [
"slice-literals.go"
],
- "sha1": "6c12749cd08a72bbdef593a7c7a81b9d863afb10",
+ "patch": [
+ "diff --git a/slice-literals.go b/slice-literals.go",
+ "index 39a2067..4555163 100644",
+ "--- a/slice-literals.go",
+ "+++ b/slice-literals.go",
+ "@@ -1,8 +1,8 @@",
+ "-const s1 = []string{}",
+ "-const s2 = []string{\"hi\"}",
+ "+const s1 = []string{\"sup\"}",
+ "+const s2 = []string{\"hello\"}",
+ " const s3 = []string{",
+ "-\"hi\",",
+ "- \"hello\",",
+ "+\"bar\",",
+ "+ \"baz\",",
+ " }",
+ " const s1 = []string{}",
+ " const s2 = []string{\"hi\"}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "988fbb38958d9dc24e4e35b23bccdad8442f4a94"
+ "shas": "6d5b83fd5bcf434b3dc818de211b89abee2d6cf4..9a675a67b7a1a6c55dcd56919a18b1cef6a4ebd2"
}
,{
"testCaseDescription": "go-slice-literals-delete-replacement-test",
@@ -422,11 +491,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
27
]
}
@@ -437,11 +506,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
29
]
}
@@ -452,11 +521,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -467,11 +536,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
22
]
}
@@ -482,11 +551,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
1
],
"end": [
- 10,
+ 8,
26
]
}
@@ -497,11 +566,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 14,
+ 12,
2
]
}
@@ -512,11 +581,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
27
]
}
@@ -527,11 +596,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
1
],
"end": [
- 10,
+ 8,
29
]
}
@@ -542,11 +611,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
1
],
"end": [
- 14,
+ 12,
2
]
}
@@ -560,9 +629,37 @@
"filePaths": [
"slice-literals.go"
],
- "sha1": "988fbb38958d9dc24e4e35b23bccdad8442f4a94",
+ "patch": [
+ "diff --git a/slice-literals.go b/slice-literals.go",
+ "index 4555163..d3fb29c 100644",
+ "--- a/slice-literals.go",
+ "+++ b/slice-literals.go",
+ "@@ -1,18 +1,12 @@",
+ "-const s1 = []string{\"sup\"}",
+ "-const s2 = []string{\"hello\"}",
+ "-const s3 = []string{",
+ "-\"bar\",",
+ "- \"baz\",",
+ "-}",
+ " const s1 = []string{}",
+ " const s2 = []string{\"hi\"}",
+ " const s3 = []string{",
+ " \"hi\",",
+ " \"hello\",",
+ " }",
+ "-const s1 = []string{}",
+ "-const s2 = []string{\"hi\"}",
+ "+const s1 = []string{\"sup\"}",
+ "+const s2 = []string{\"hello\"}",
+ " const s3 = []string{",
+ "-\"hi\",",
+ "- \"hello\",",
+ "+\"bar\",",
+ "+ \"baz\",",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e138f6bad52e3a5eb9669b55644cf0f6b78a4959"
+ "shas": "9a675a67b7a1a6c55dcd56919a18b1cef6a4ebd2..0be08b31a19a03e3ab9ce42f685dac31c88fcf21"
}
,{
"testCaseDescription": "go-slice-literals-delete-test",
@@ -573,11 +670,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -588,11 +685,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
26
]
}
@@ -603,11 +700,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -621,9 +718,24 @@
"filePaths": [
"slice-literals.go"
],
- "sha1": "e138f6bad52e3a5eb9669b55644cf0f6b78a4959",
+ "patch": [
+ "diff --git a/slice-literals.go b/slice-literals.go",
+ "index d3fb29c..e3fd378 100644",
+ "--- a/slice-literals.go",
+ "+++ b/slice-literals.go",
+ "@@ -1,9 +1,3 @@",
+ "-const s1 = []string{}",
+ "-const s2 = []string{\"hi\"}",
+ "-const s3 = []string{",
+ "-\"hi\",",
+ "- \"hello\",",
+ "-}",
+ " const s1 = []string{\"sup\"}",
+ " const s2 = []string{\"hello\"}",
+ " const s3 = []string{"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7cc41f942596210a56b0d38f340cbbff25e64125"
+ "shas": "0be08b31a19a03e3ab9ce42f685dac31c88fcf21..3aa336f26d89c944f5f2d3ce3382a451a2e9ab9c"
}
,{
"testCaseDescription": "go-slice-literals-delete-rest-test",
@@ -634,11 +746,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
27
]
}
@@ -649,11 +761,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
29
]
}
@@ -664,11 +776,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 8,
+ 6,
2
]
}
@@ -682,7 +794,19 @@
"filePaths": [
"slice-literals.go"
],
- "sha1": "7cc41f942596210a56b0d38f340cbbff25e64125",
+ "patch": [
+ "diff --git a/slice-literals.go b/slice-literals.go",
+ "index e3fd378..e69de29 100644",
+ "--- a/slice-literals.go",
+ "+++ b/slice-literals.go",
+ "@@ -1,6 +0,0 @@",
+ "-const s1 = []string{\"sup\"}",
+ "-const s2 = []string{\"hello\"}",
+ "-const s3 = []string{",
+ "-\"bar\",",
+ "- \"baz\",",
+ "-}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ac21f9d0ee6f7ef2a5a607b08fe2b95f3a6470c8"
+ "shas": "3aa336f26d89c944f5f2d3ce3382a451a2e9ab9c..5b7d43722e8258820bec8f43f32d77913026fbd1"
}]
diff --git a/test/corpus/diff-summaries/go/slice-types.json b/test/corpus/diff-summaries/go/slice-types.json
index a39ad04cf..6ca6abbda 100644
--- a/test/corpus/diff-summaries/go/slice-types.json
+++ b/test/corpus/diff-summaries/go/slice-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
}
@@ -70,9 +70,17 @@
"filePaths": [
"slice-types.go"
],
- "sha1": "4c8c99e5a735f66e43d41e65a75a75272a162c8c",
+ "patch": [
+ "diff --git a/slice-types.go b/slice-types.go",
+ "index e69de29..1b8dbe5 100644",
+ "--- a/slice-types.go",
+ "+++ b/slice-types.go",
+ "@@ -0,0 +1,2 @@",
+ "+type a []b",
+ "+type c [][]d"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "99a3831a6044a4a67c3097d126a27802bf1a070b"
+ "shas": "338fc2d73f62d9c316e48cf2390c1052834d4985..1ea577f2f81489221ed09ffb1ad11075a01a8c3c"
}
,{
"testCaseDescription": "go-slice-types-replacement-insert-test",
@@ -83,11 +91,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -98,11 +106,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
13
]
}
@@ -113,11 +121,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -128,11 +136,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -143,11 +151,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
@@ -158,11 +166,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
10
],
"end": [
- 5,
+ 3,
11
]
}
@@ -173,11 +181,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -188,11 +196,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
12
],
"end": [
- 6,
+ 4,
13
]
}
@@ -206,9 +214,21 @@
"filePaths": [
"slice-types.go"
],
- "sha1": "99a3831a6044a4a67c3097d126a27802bf1a070b",
+ "patch": [
+ "diff --git a/slice-types.go b/slice-types.go",
+ "index 1b8dbe5..d718ee8 100644",
+ "--- a/slice-types.go",
+ "+++ b/slice-types.go",
+ "@@ -1,2 +1,6 @@",
+ "+type a [][]p",
+ "+type c []y",
+ "+type a []b",
+ "+type c [][]d",
+ " type a []b",
+ " type c [][]d"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "cc90097c8cf3490855377cf31aa3de2e3e92b08f"
+ "shas": "1ea577f2f81489221ed09ffb1ad11075a01a8c3c..ea4858c48ca03ca912291083660d83d19205240c"
}
,{
"testCaseDescription": "go-slice-types-delete-insert-test",
@@ -219,11 +239,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
}
@@ -234,11 +254,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
13
]
}
@@ -249,11 +269,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
}
@@ -264,11 +284,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -282,9 +302,22 @@
"filePaths": [
"slice-types.go"
],
- "sha1": "cc90097c8cf3490855377cf31aa3de2e3e92b08f",
+ "patch": [
+ "diff --git a/slice-types.go b/slice-types.go",
+ "index d718ee8..e6836eb 100644",
+ "--- a/slice-types.go",
+ "+++ b/slice-types.go",
+ "@@ -1,5 +1,5 @@",
+ "-type a [][]p",
+ "-type c []y",
+ "+type a []b",
+ "+type c [][]d",
+ " type a []b",
+ " type c [][]d",
+ " type a []b"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b7bd35a7d0885f272b4308903892645a3fe5bbb7"
+ "shas": "ea4858c48ca03ca912291083660d83d19205240c..74a3b7c7d6431de72a0ab9d1fe827fb9207385bb"
}
,{
"testCaseDescription": "go-slice-types-replacement-test",
@@ -295,11 +328,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
13
]
}
@@ -310,11 +343,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
}
@@ -325,11 +358,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -340,11 +373,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
}
@@ -358,9 +391,22 @@
"filePaths": [
"slice-types.go"
],
- "sha1": "b7bd35a7d0885f272b4308903892645a3fe5bbb7",
+ "patch": [
+ "diff --git a/slice-types.go b/slice-types.go",
+ "index e6836eb..d718ee8 100644",
+ "--- a/slice-types.go",
+ "+++ b/slice-types.go",
+ "@@ -1,5 +1,5 @@",
+ "-type a []b",
+ "-type c [][]d",
+ "+type a [][]p",
+ "+type c []y",
+ " type a []b",
+ " type c [][]d",
+ " type a []b"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7e67518ac3811296fdc770c881b134581998c9cd"
+ "shas": "74a3b7c7d6431de72a0ab9d1fe827fb9207385bb..3c1f3f0aaba3f93566e81fa6919588140c7f84f8"
}
,{
"testCaseDescription": "go-slice-types-delete-replacement-test",
@@ -371,11 +417,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -386,11 +432,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
13
]
}
@@ -401,11 +447,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -416,11 +462,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -431,11 +477,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
@@ -446,11 +492,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
10
],
"end": [
- 5,
+ 3,
11
]
}
@@ -461,11 +507,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -476,11 +522,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
12
],
"end": [
- 6,
+ 4,
13
]
}
@@ -491,11 +537,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
@@ -506,11 +552,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
12
],
"end": [
- 5,
+ 3,
13
]
}
@@ -521,11 +567,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
7
]
}
@@ -536,11 +582,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
10
],
"end": [
- 6,
+ 4,
11
]
}
@@ -554,9 +600,23 @@
"filePaths": [
"slice-types.go"
],
- "sha1": "7e67518ac3811296fdc770c881b134581998c9cd",
+ "patch": [
+ "diff --git a/slice-types.go b/slice-types.go",
+ "index d718ee8..9f9c73f 100644",
+ "--- a/slice-types.go",
+ "+++ b/slice-types.go",
+ "@@ -1,6 +1,4 @@",
+ "-type a [][]p",
+ "-type c []y",
+ "-type a []b",
+ "-type c [][]d",
+ " type a []b",
+ " type c [][]d",
+ "+type a [][]p",
+ "+type c []y"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "5fc6c996739c83c3b77acfb9fcd7e89ee3ffe347"
+ "shas": "3c1f3f0aaba3f93566e81fa6919588140c7f84f8..14884815c9c60888a7434f5537b7d37ed222154b"
}
,{
"testCaseDescription": "go-slice-types-delete-test",
@@ -567,11 +627,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -582,11 +642,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
10
],
"end": [
- 3,
+ 1,
11
]
}
@@ -597,11 +657,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -612,11 +672,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
}
@@ -630,9 +690,19 @@
"filePaths": [
"slice-types.go"
],
- "sha1": "5fc6c996739c83c3b77acfb9fcd7e89ee3ffe347",
+ "patch": [
+ "diff --git a/slice-types.go b/slice-types.go",
+ "index 9f9c73f..964a319 100644",
+ "--- a/slice-types.go",
+ "+++ b/slice-types.go",
+ "@@ -1,4 +1,2 @@",
+ "-type a []b",
+ "-type c [][]d",
+ " type a [][]p",
+ " type c []y"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "16fcb96325446aa55183c41f179fb38b2288c374"
+ "shas": "14884815c9c60888a7434f5537b7d37ed222154b..9052f7f67fe0ab24fccfccd64c631ce9a5ea299d"
}
,{
"testCaseDescription": "go-slice-types-delete-rest-test",
@@ -643,11 +713,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -658,11 +728,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
13
]
}
@@ -673,11 +743,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
@@ -688,11 +758,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -706,7 +776,15 @@
"filePaths": [
"slice-types.go"
],
- "sha1": "16fcb96325446aa55183c41f179fb38b2288c374",
+ "patch": [
+ "diff --git a/slice-types.go b/slice-types.go",
+ "index 964a319..e69de29 100644",
+ "--- a/slice-types.go",
+ "+++ b/slice-types.go",
+ "@@ -1,2 +0,0 @@",
+ "-type a [][]p",
+ "-type c []y"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "776befbec12285642ba8944297803b4289c10cf0"
+ "shas": "9052f7f67fe0ab24fccfccd64c631ce9a5ea299d..32e685f38686a99987e01d66161451aeba15b018"
}]
diff --git a/test/corpus/diff-summaries/go/string-literals.json b/test/corpus/diff-summaries/go/string-literals.json
index f1af5edb6..e6f52fe43 100644
--- a/test/corpus/diff-summaries/go/string-literals.json
+++ b/test/corpus/diff-summaries/go/string-literals.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -40,9 +40,19 @@
"filePaths": [
"string-literals.go"
],
- "sha1": "46503417695204e939923a09702395449f526a66",
+ "patch": [
+ "diff --git a/string-literals.go b/string-literals.go",
+ "index e69de29..90ac543 100644",
+ "--- a/string-literals.go",
+ "+++ b/string-literals.go",
+ "@@ -0,0 +1,4 @@",
+ "+const (",
+ "+a = \"0\"",
+ "+b = \"hello world\"",
+ "+)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a76939c67983d066f688e7ce631efa7939b44061"
+ "shas": "3f18376b34b25deb3740a62df8c40ad667cfef4a..1fcc677f0888042248bdab575c0e47c0ab14de18"
}
,{
"testCaseDescription": "go-string-literals-replacement-insert-test",
@@ -53,11 +63,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -68,11 +78,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -83,11 +93,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -98,11 +108,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -116,9 +126,27 @@
"filePaths": [
"string-literals.go"
],
- "sha1": "a76939c67983d066f688e7ce631efa7939b44061",
+ "patch": [
+ "diff --git a/string-literals.go b/string-literals.go",
+ "index 90ac543..a781ce7 100644",
+ "--- a/string-literals.go",
+ "+++ b/string-literals.go",
+ "@@ -1,4 +1,12 @@",
+ " const (",
+ "+a = \"2\"",
+ "+b = \"hi\"",
+ "+)",
+ "+const (",
+ "+a = \"0\"",
+ "+b = \"hello world\"",
+ "+)",
+ "+const (",
+ " a = \"0\"",
+ " b = \"hello world\"",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "2ee4fc2288f35ae53ff82ea8c0e635e6c8ec88fb"
+ "shas": "1fcc677f0888042248bdab575c0e47c0ab14de18..b2d8cadd90f5b59b4c6eb0390c490ae2c4a18d43"
}
,{
"testCaseDescription": "go-string-literals-delete-insert-test",
@@ -130,54 +158,54 @@
"replace": [
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
}
]
},
- "summary": "Replaced the \"2\" string with the \"0\" string in the a variable of the 'main' module"
+ "summary": "Replaced the \"2\" string with the \"0\" string in the a variable"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
9
]
},
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
18
]
}
]
},
- "summary": "Replaced the \"hi\" string with the \"hello world\" string in the b variable of the 'main' module"
+ "summary": "Replaced the \"hi\" string with the \"hello world\" string in the b variable"
}
]
},
@@ -186,9 +214,23 @@
"filePaths": [
"string-literals.go"
],
- "sha1": "2ee4fc2288f35ae53ff82ea8c0e635e6c8ec88fb",
+ "patch": [
+ "diff --git a/string-literals.go b/string-literals.go",
+ "index a781ce7..e7b83ba 100644",
+ "--- a/string-literals.go",
+ "+++ b/string-literals.go",
+ "@@ -1,6 +1,6 @@",
+ " const (",
+ "-a = \"2\"",
+ "-b = \"hi\"",
+ "+a = \"0\"",
+ "+b = \"hello world\"",
+ " )",
+ " const (",
+ " a = \"0\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a9289dc489299bca159b46cf38d70d86dbdaec2b"
+ "shas": "b2d8cadd90f5b59b4c6eb0390c490ae2c4a18d43..a1f9c06d180e286202d36246299acd0b591fcd5a"
}
,{
"testCaseDescription": "go-string-literals-replacement-test",
@@ -200,54 +242,54 @@
"replace": [
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
}
]
},
- "summary": "Replaced the \"0\" string with the \"2\" string in the a variable of the 'main' module"
+ "summary": "Replaced the \"0\" string with the \"2\" string in the a variable"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
18
]
},
{
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
9
]
}
]
},
- "summary": "Replaced the \"hello world\" string with the \"hi\" string in the b variable of the 'main' module"
+ "summary": "Replaced the \"hello world\" string with the \"hi\" string in the b variable"
}
]
},
@@ -256,9 +298,23 @@
"filePaths": [
"string-literals.go"
],
- "sha1": "a9289dc489299bca159b46cf38d70d86dbdaec2b",
+ "patch": [
+ "diff --git a/string-literals.go b/string-literals.go",
+ "index e7b83ba..a781ce7 100644",
+ "--- a/string-literals.go",
+ "+++ b/string-literals.go",
+ "@@ -1,6 +1,6 @@",
+ " const (",
+ "-a = \"0\"",
+ "-b = \"hello world\"",
+ "+a = \"2\"",
+ "+b = \"hi\"",
+ " )",
+ " const (",
+ " a = \"0\""
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "1b4e94355841b5a0f04871f29b45eaacfae619b7"
+ "shas": "a1f9c06d180e286202d36246299acd0b591fcd5a..e1282339ed365981efd8f8c59b43478999306c11"
}
,{
"testCaseDescription": "go-string-literals-delete-replacement-test",
@@ -269,11 +325,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -284,11 +340,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -299,11 +355,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -314,11 +370,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -329,11 +385,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -344,11 +400,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 10,
+ 8,
2
]
}
@@ -362,9 +418,29 @@
"filePaths": [
"string-literals.go"
],
- "sha1": "1b4e94355841b5a0f04871f29b45eaacfae619b7",
+ "patch": [
+ "diff --git a/string-literals.go b/string-literals.go",
+ "index a781ce7..38c651f 100644",
+ "--- a/string-literals.go",
+ "+++ b/string-literals.go",
+ "@@ -1,12 +1,8 @@",
+ " const (",
+ "-a = \"2\"",
+ "-b = \"hi\"",
+ "-)",
+ "-const (",
+ " a = \"0\"",
+ " b = \"hello world\"",
+ " )",
+ " const (",
+ "-a = \"0\"",
+ "-b = \"hello world\"",
+ "+a = \"2\"",
+ "+b = \"hi\"",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "2ee868c0d8265081b782f2a44910abb7093a0c0c"
+ "shas": "e1282339ed365981efd8f8c59b43478999306c11..432f3a0fcc0b325bc03132ce27f83e25fe8be1ae"
}
,{
"testCaseDescription": "go-string-literals-delete-test",
@@ -375,11 +451,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -390,11 +466,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -408,9 +484,23 @@
"filePaths": [
"string-literals.go"
],
- "sha1": "2ee868c0d8265081b782f2a44910abb7093a0c0c",
+ "patch": [
+ "diff --git a/string-literals.go b/string-literals.go",
+ "index 38c651f..f70bc80 100644",
+ "--- a/string-literals.go",
+ "+++ b/string-literals.go",
+ "@@ -1,8 +1,4 @@",
+ " const (",
+ "-a = \"0\"",
+ "-b = \"hello world\"",
+ "-)",
+ "-const (",
+ " a = \"2\"",
+ " b = \"hi\"",
+ " )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "1a592735bca17371b66c085235fb6cc6bb00b321"
+ "shas": "432f3a0fcc0b325bc03132ce27f83e25fe8be1ae..42c2e3f4eef81d189311a542d1c0450e8b56c443"
}
,{
"testCaseDescription": "go-string-literals-delete-rest-test",
@@ -421,11 +511,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -436,11 +526,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -454,7 +544,17 @@
"filePaths": [
"string-literals.go"
],
- "sha1": "1a592735bca17371b66c085235fb6cc6bb00b321",
+ "patch": [
+ "diff --git a/string-literals.go b/string-literals.go",
+ "index f70bc80..e69de29 100644",
+ "--- a/string-literals.go",
+ "+++ b/string-literals.go",
+ "@@ -1,4 +0,0 @@",
+ "-const (",
+ "-a = \"2\"",
+ "-b = \"hi\"",
+ "-)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e727d68d5530b584f126dc2c23f5dafc2ed9f862"
+ "shas": "42c2e3f4eef81d189311a542d1c0450e8b56c443..9e795da07ee62f0a45cb22c279f0ac4a7f3d43d7"
}]
diff --git a/test/corpus/diff-summaries/go/struct-literals.json b/test/corpus/diff-summaries/go/struct-literals.json
index c35b4b54b..9f8364cd2 100644
--- a/test/corpus/diff-summaries/go/struct-literals.json
+++ b/test/corpus/diff-summaries/go/struct-literals.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
32
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
23
]
}
@@ -55,9 +55,21 @@
"filePaths": [
"struct-literals.go"
],
- "sha1": "bb9bc3e6100eaaf7ccd25a9360f08698cff15981",
+ "patch": [
+ "diff --git a/struct-literals.go b/struct-literals.go",
+ "index e69de29..f949dbb 100644",
+ "--- a/struct-literals.go",
+ "+++ b/struct-literals.go",
+ "@@ -0,0 +1,6 @@",
+ "+const s1 = Person{",
+ "+name: \"Frank\",",
+ "+Age: \"5 months\",",
+ "+}",
+ "+const s2 = struct{i int;}{i: 5}",
+ "+const s3 = time.Time{}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "5751915de93bd4edbb76549621e27487401e9ddc"
+ "shas": "cd582e9b85e985f87af52085296e006987e8b0d3..6c9bcc47bf47a86de621d89270a4d7d62dd8241c"
}
,{
"testCaseDescription": "go-struct-literals-replacement-insert-test",
@@ -68,11 +80,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -83,11 +95,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
34
]
}
@@ -98,11 +110,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
24
]
}
@@ -113,11 +125,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 12,
+ 10,
2
]
}
@@ -128,11 +140,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 11,
1
],
"end": [
- 13,
+ 11,
32
]
}
@@ -143,11 +155,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 12,
1
],
"end": [
- 14,
+ 12,
23
]
}
@@ -161,9 +173,30 @@
"filePaths": [
"struct-literals.go"
],
- "sha1": "5751915de93bd4edbb76549621e27487401e9ddc",
+ "patch": [
+ "diff --git a/struct-literals.go b/struct-literals.go",
+ "index f949dbb..c6a242e 100644",
+ "--- a/struct-literals.go",
+ "+++ b/struct-literals.go",
+ "@@ -1,3 +1,15 @@",
+ "+const s1 = Dog{",
+ "+name: \"Frank\",",
+ "+Age: \"5 months\",",
+ "+}",
+ "+const s2 = struct{i float;}{j: 6}",
+ "+const s3 = time.Month{}",
+ "+const s1 = Person{",
+ "+name: \"Frank\",",
+ "+Age: \"5 months\",",
+ "+}",
+ "+const s2 = struct{i int;}{i: 5}",
+ "+const s3 = time.Time{}",
+ " const s1 = Person{",
+ " name: \"Frank\",",
+ " Age: \"5 months\","
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "0ac865f0373e18dd0b54761f3e7b229a8aeedcb7"
+ "shas": "6c9bcc47bf47a86de621d89270a4d7d62dd8241c..549bd62659cc4988bc02a8deb069747ea8efc519"
}
,{
"testCaseDescription": "go-struct-literals-delete-insert-test",
@@ -175,135 +208,135 @@
"replace": [
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
15
]
},
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
18
]
}
]
},
- "summary": "Replaced the 'Dog' identifier with the 'Person' identifier in the s1 variable of the 'main' module"
+ "summary": "Replaced the 'Dog' identifier with the 'Person' identifier in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
- 7,
+ 5,
21
],
"end": [
- 7,
+ 5,
26
]
},
{
"start": [
- 7,
+ 5,
21
],
"end": [
- 7,
+ 5,
24
]
}
]
},
- "summary": "Replaced the 'float' identifier with the 'int' identifier in the s2 variable of the 'main' module"
+ "summary": "Replaced the 'float' identifier with the 'int' identifier in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
- 7,
+ 5,
29
],
"end": [
- 7,
+ 5,
30
]
},
{
"start": [
- 7,
+ 5,
27
],
"end": [
- 7,
+ 5,
28
]
}
]
},
- "summary": "Replaced the 'j' identifier with the 'i' identifier in the s2 variable of the 'main' module"
+ "summary": "Replaced the 'j' identifier with the 'i' identifier in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
- 7,
+ 5,
32
],
"end": [
- 7,
+ 5,
33
]
},
{
"start": [
- 7,
+ 5,
30
],
"end": [
- 7,
+ 5,
31
]
}
]
},
- "summary": "Replaced '6' with '5' in the s2 variable of the 'main' module"
+ "summary": "Replaced '6' with '5' in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
- 8,
+ 6,
17
],
"end": [
- 8,
+ 6,
22
]
},
{
"start": [
- 8,
+ 6,
17
],
"end": [
- 8,
+ 6,
21
]
}
]
},
- "summary": "Replaced the 'Month' identifier with the 'Time' identifier in the s3 variable of the 'main' module"
+ "summary": "Replaced the 'Month' identifier with the 'Time' identifier in the s3 variable"
}
]
},
@@ -312,9 +345,27 @@
"filePaths": [
"struct-literals.go"
],
- "sha1": "0ac865f0373e18dd0b54761f3e7b229a8aeedcb7",
+ "patch": [
+ "diff --git a/struct-literals.go b/struct-literals.go",
+ "index c6a242e..680652e 100644",
+ "--- a/struct-literals.go",
+ "+++ b/struct-literals.go",
+ "@@ -1,9 +1,9 @@",
+ "-const s1 = Dog{",
+ "+const s1 = Person{",
+ " name: \"Frank\",",
+ " Age: \"5 months\",",
+ " }",
+ "-const s2 = struct{i float;}{j: 6}",
+ "-const s3 = time.Month{}",
+ "+const s2 = struct{i int;}{i: 5}",
+ "+const s3 = time.Time{}",
+ " const s1 = Person{",
+ " name: \"Frank\",",
+ " Age: \"5 months\","
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "156014fcaa38d31c2fde2e7fb290c8f4b2b636ba"
+ "shas": "549bd62659cc4988bc02a8deb069747ea8efc519..02d890ec6a09db8058f6a825c4f81f4c0abcfa38"
}
,{
"testCaseDescription": "go-struct-literals-replacement-test",
@@ -326,135 +377,135 @@
"replace": [
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
18
]
},
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
15
]
}
]
},
- "summary": "Replaced the 'Person' identifier with the 'Dog' identifier in the s1 variable of the 'main' module"
+ "summary": "Replaced the 'Person' identifier with the 'Dog' identifier in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
- 7,
+ 5,
21
],
"end": [
- 7,
+ 5,
24
]
},
{
"start": [
- 7,
+ 5,
21
],
"end": [
- 7,
+ 5,
26
]
}
]
},
- "summary": "Replaced the 'int' identifier with the 'float' identifier in the s2 variable of the 'main' module"
+ "summary": "Replaced the 'int' identifier with the 'float' identifier in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
- 7,
+ 5,
27
],
"end": [
- 7,
+ 5,
28
]
},
{
"start": [
- 7,
+ 5,
29
],
"end": [
- 7,
+ 5,
30
]
}
]
},
- "summary": "Replaced the 'i' identifier with the 'j' identifier in the s2 variable of the 'main' module"
+ "summary": "Replaced the 'i' identifier with the 'j' identifier in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
- 7,
+ 5,
30
],
"end": [
- 7,
+ 5,
31
]
},
{
"start": [
- 7,
+ 5,
32
],
"end": [
- 7,
+ 5,
33
]
}
]
},
- "summary": "Replaced '5' with '6' in the s2 variable of the 'main' module"
+ "summary": "Replaced '5' with '6' in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
- 8,
+ 6,
17
],
"end": [
- 8,
+ 6,
21
]
},
{
"start": [
- 8,
+ 6,
17
],
"end": [
- 8,
+ 6,
22
]
}
]
},
- "summary": "Replaced the 'Time' identifier with the 'Month' identifier in the s3 variable of the 'main' module"
+ "summary": "Replaced the 'Time' identifier with the 'Month' identifier in the s3 variable"
}
]
},
@@ -463,9 +514,27 @@
"filePaths": [
"struct-literals.go"
],
- "sha1": "156014fcaa38d31c2fde2e7fb290c8f4b2b636ba",
+ "patch": [
+ "diff --git a/struct-literals.go b/struct-literals.go",
+ "index 680652e..c6a242e 100644",
+ "--- a/struct-literals.go",
+ "+++ b/struct-literals.go",
+ "@@ -1,9 +1,9 @@",
+ "-const s1 = Person{",
+ "+const s1 = Dog{",
+ " name: \"Frank\",",
+ " Age: \"5 months\",",
+ " }",
+ "-const s2 = struct{i int;}{i: 5}",
+ "-const s3 = time.Time{}",
+ "+const s2 = struct{i float;}{j: 6}",
+ "+const s3 = time.Month{}",
+ " const s1 = Person{",
+ " name: \"Frank\",",
+ " Age: \"5 months\","
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "174afee30e6ac3bdc677dabaccec0fbc080702f2"
+ "shas": "02d890ec6a09db8058f6a825c4f81f4c0abcfa38..3e8f6a306606b2698b9733e5f66cd359a7563b3d"
}
,{
"testCaseDescription": "go-struct-literals-delete-replacement-test",
@@ -476,11 +545,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -491,11 +560,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
34
]
}
@@ -506,11 +575,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
24
]
}
@@ -521,11 +590,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 12,
+ 10,
2
]
}
@@ -536,11 +605,11 @@
"span": {
"delete": {
"start": [
- 13,
+ 11,
1
],
"end": [
- 13,
+ 11,
32
]
}
@@ -551,11 +620,11 @@
"span": {
"delete": {
"start": [
- 14,
+ 12,
1
],
"end": [
- 14,
+ 12,
23
]
}
@@ -566,11 +635,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 12,
+ 10,
2
]
}
@@ -581,11 +650,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 11,
1
],
"end": [
- 13,
+ 11,
34
]
}
@@ -596,11 +665,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 12,
1
],
"end": [
- 14,
+ 12,
24
]
}
@@ -614,9 +683,36 @@
"filePaths": [
"struct-literals.go"
],
- "sha1": "174afee30e6ac3bdc677dabaccec0fbc080702f2",
+ "patch": [
+ "diff --git a/struct-literals.go b/struct-literals.go",
+ "index c6a242e..5aaf236 100644",
+ "--- a/struct-literals.go",
+ "+++ b/struct-literals.go",
+ "@@ -1,18 +1,12 @@",
+ "-const s1 = Dog{",
+ "-name: \"Frank\",",
+ "-Age: \"5 months\",",
+ "-}",
+ "-const s2 = struct{i float;}{j: 6}",
+ "-const s3 = time.Month{}",
+ " const s1 = Person{",
+ " name: \"Frank\",",
+ " Age: \"5 months\",",
+ " }",
+ " const s2 = struct{i int;}{i: 5}",
+ " const s3 = time.Time{}",
+ "-const s1 = Person{",
+ "+const s1 = Dog{",
+ " name: \"Frank\",",
+ " Age: \"5 months\",",
+ " }",
+ "-const s2 = struct{i int;}{i: 5}",
+ "-const s3 = time.Time{}",
+ "+const s2 = struct{i float;}{j: 6}",
+ "+const s3 = time.Month{}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "603e16c70c2ac01320ed82cde555516397b7861a"
+ "shas": "3e8f6a306606b2698b9733e5f66cd359a7563b3d..9e036681bd0abc57a429a77198d02f726efff075"
}
,{
"testCaseDescription": "go-struct-literals-delete-test",
@@ -627,11 +723,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -642,11 +738,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
32
]
}
@@ -657,11 +753,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
23
]
}
@@ -675,9 +771,24 @@
"filePaths": [
"struct-literals.go"
],
- "sha1": "603e16c70c2ac01320ed82cde555516397b7861a",
+ "patch": [
+ "diff --git a/struct-literals.go b/struct-literals.go",
+ "index 5aaf236..9f5ac64 100644",
+ "--- a/struct-literals.go",
+ "+++ b/struct-literals.go",
+ "@@ -1,9 +1,3 @@",
+ "-const s1 = Person{",
+ "-name: \"Frank\",",
+ "-Age: \"5 months\",",
+ "-}",
+ "-const s2 = struct{i int;}{i: 5}",
+ "-const s3 = time.Time{}",
+ " const s1 = Dog{",
+ " name: \"Frank\",",
+ " Age: \"5 months\","
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3c9c55133ad8c871ab1b2b9704781762203f8a7b"
+ "shas": "9e036681bd0abc57a429a77198d02f726efff075..0cabca264829090bbcca8324cad7d2ef6d0a4c1c"
}
,{
"testCaseDescription": "go-struct-literals-delete-rest-test",
@@ -688,11 +799,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -703,11 +814,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
34
]
}
@@ -718,11 +829,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
24
]
}
@@ -736,7 +847,19 @@
"filePaths": [
"struct-literals.go"
],
- "sha1": "3c9c55133ad8c871ab1b2b9704781762203f8a7b",
+ "patch": [
+ "diff --git a/struct-literals.go b/struct-literals.go",
+ "index 9f5ac64..e69de29 100644",
+ "--- a/struct-literals.go",
+ "+++ b/struct-literals.go",
+ "@@ -1,6 +0,0 @@",
+ "-const s1 = Dog{",
+ "-name: \"Frank\",",
+ "-Age: \"5 months\",",
+ "-}",
+ "-const s2 = struct{i float;}{j: 6}",
+ "-const s3 = time.Month{}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a4eb90cc8a9cbf4002ab1c646f3b965bce70cc47"
+ "shas": "0cabca264829090bbcca8324cad7d2ef6d0a4c1c..1afdfc9d2ffbe4b43ec47892c4583237f382efd2"
}]
diff --git a/test/corpus/diff-summaries/go/struct-types.json b/test/corpus/diff-summaries/go/struct-types.json
index fa07fa801..520f7afaf 100644
--- a/test/corpus/diff-summaries/go/struct-types.json
+++ b/test/corpus/diff-summaries/go/struct-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
18
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
18
],
"end": [
- 4,
+ 2,
24
]
}
@@ -67,11 +67,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -82,11 +82,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -97,11 +97,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -112,11 +112,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
9
]
}
@@ -127,11 +127,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
}
@@ -142,11 +142,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
2
]
}
@@ -157,11 +157,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
3
],
"end": [
- 9,
+ 7,
5
]
}
@@ -172,11 +172,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
2
],
"end": [
- 10,
+ 8,
3
]
}
@@ -187,11 +187,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
4
],
"end": [
- 10,
+ 8,
7
]
}
@@ -202,11 +202,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
8
],
"end": [
- 10,
+ 8,
18
]
}
@@ -220,9 +220,24 @@
"filePaths": [
"struct-types.go"
],
- "sha1": "776befbec12285642ba8944297803b4289c10cf0",
+ "patch": [
+ "diff --git a/struct-types.go b/struct-types.go",
+ "index e69de29..d381002 100644",
+ "--- a/struct-types.go",
+ "+++ b/struct-types.go",
+ "@@ -0,0 +1,9 @@",
+ "+type s1 struct {}",
+ "+type s2 struct { Person }",
+ "+type s3 struct {",
+ "+f, g int",
+ "+}",
+ "+type s4 struct {",
+ "+p.s1",
+ "+ h int `json:\"h\"`",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e5f48b82f8b857cfda5740b0fcb36ce50f36ba28"
+ "shas": "32e685f38686a99987e01d66161451aeba15b018..56960223a1eb47bc34a55ac7a56c535293ae34ed"
}
,{
"testCaseDescription": "go-struct-types-replacement-insert-test",
@@ -233,11 +248,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -248,11 +263,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
18
]
}
@@ -263,11 +278,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -278,11 +293,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
18
],
"end": [
- 4,
+ 2,
24
]
}
@@ -293,11 +308,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -308,11 +323,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -323,11 +338,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -338,11 +353,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
9
]
}
@@ -353,11 +368,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
}
@@ -368,11 +383,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
2
]
}
@@ -383,11 +398,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
3
],
"end": [
- 9,
+ 7,
5
]
}
@@ -398,11 +413,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
2
],
"end": [
- 10,
+ 8,
3
]
}
@@ -413,11 +428,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
4
],
"end": [
- 10,
+ 8,
7
]
}
@@ -428,11 +443,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
8
],
"end": [
- 10,
+ 8,
18
]
}
@@ -443,11 +458,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
6
],
"end": [
- 12,
+ 10,
8
]
}
@@ -458,11 +473,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
9
],
"end": [
- 12,
+ 10,
18
]
}
@@ -473,11 +488,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 11,
6
],
"end": [
- 13,
+ 11,
8
]
}
@@ -488,11 +503,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 11,
18
],
"end": [
- 13,
+ 11,
24
]
}
@@ -503,11 +518,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 12,
6
],
"end": [
- 14,
+ 12,
8
]
}
@@ -518,11 +533,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
1
],
"end": [
- 15,
+ 13,
2
]
}
@@ -533,11 +548,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
4
],
"end": [
- 15,
+ 13,
5
]
}
@@ -548,11 +563,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
6
],
"end": [
- 15,
+ 13,
9
]
}
@@ -563,11 +578,11 @@
"span": {
"insert": {
"start": [
- 17,
+ 15,
6
],
"end": [
- 17,
+ 15,
8
]
}
@@ -578,11 +593,11 @@
"span": {
"insert": {
"start": [
- 18,
+ 16,
1
],
"end": [
- 18,
+ 16,
2
]
}
@@ -593,11 +608,11 @@
"span": {
"insert": {
"start": [
- 18,
+ 16,
3
],
"end": [
- 18,
+ 16,
5
]
}
@@ -608,11 +623,11 @@
"span": {
"insert": {
"start": [
- 19,
+ 17,
2
],
"end": [
- 19,
+ 17,
3
]
}
@@ -623,11 +638,11 @@
"span": {
"insert": {
"start": [
- 19,
+ 17,
4
],
"end": [
- 19,
+ 17,
7
]
}
@@ -638,11 +653,11 @@
"span": {
"insert": {
"start": [
- 19,
+ 17,
8
],
"end": [
- 19,
+ 17,
18
]
}
@@ -656,9 +671,36 @@
"filePaths": [
"struct-types.go"
],
- "sha1": "e5f48b82f8b857cfda5740b0fcb36ce50f36ba28",
+ "patch": [
+ "diff --git a/struct-types.go b/struct-types.go",
+ "index d381002..e1f6f1a 100644",
+ "--- a/struct-types.go",
+ "+++ b/struct-types.go",
+ "@@ -1,3 +1,21 @@",
+ "+type t1 struct {}",
+ "+type t2 struct { Person }",
+ "+type t3 struct {",
+ "+f, g int",
+ "+}",
+ "+type t4 struct {",
+ "+p.s1",
+ "+ h int `json:\"h\"`",
+ "+}",
+ "+type s1 struct {}",
+ "+type s2 struct { Person }",
+ "+type s3 struct {",
+ "+f, g int",
+ "+}",
+ "+type s4 struct {",
+ "+p.s1",
+ "+ h int `json:\"h\"`",
+ "+}",
+ " type s1 struct {}",
+ " type s2 struct { Person }",
+ " type s3 struct {"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "d7eeec516ac31880ba2f5bd047bd654498c25b15"
+ "shas": "56960223a1eb47bc34a55ac7a56c535293ae34ed..99a1cab78be883793829a6a87afb78b3ad104866"
}
,{
"testCaseDescription": "go-struct-types-delete-insert-test",
@@ -670,21 +712,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -697,21 +739,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -724,21 +766,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -751,21 +793,21 @@
"replace": [
{
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
},
{
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
}
@@ -780,9 +822,28 @@
"filePaths": [
"struct-types.go"
],
- "sha1": "d7eeec516ac31880ba2f5bd047bd654498c25b15",
+ "patch": [
+ "diff --git a/struct-types.go b/struct-types.go",
+ "index e1f6f1a..b7798e0 100644",
+ "--- a/struct-types.go",
+ "+++ b/struct-types.go",
+ "@@ -1,9 +1,9 @@",
+ "-type t1 struct {}",
+ "-type t2 struct { Person }",
+ "-type t3 struct {",
+ "+type s1 struct {}",
+ "+type s2 struct { Person }",
+ "+type s3 struct {",
+ " f, g int",
+ " }",
+ "-type t4 struct {",
+ "+type s4 struct {",
+ " p.s1",
+ " h int `json:\"h\"`",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a87620cc154106c8a2b8b535120e923f70e6db19"
+ "shas": "99a1cab78be883793829a6a87afb78b3ad104866..2f9c7f7af1b13c6dae856277d12728846ad6b21b"
}
,{
"testCaseDescription": "go-struct-types-replacement-test",
@@ -794,21 +855,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -821,21 +882,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -848,21 +909,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -875,21 +936,21 @@
"replace": [
{
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
},
{
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
}
@@ -904,9 +965,28 @@
"filePaths": [
"struct-types.go"
],
- "sha1": "a87620cc154106c8a2b8b535120e923f70e6db19",
+ "patch": [
+ "diff --git a/struct-types.go b/struct-types.go",
+ "index b7798e0..e1f6f1a 100644",
+ "--- a/struct-types.go",
+ "+++ b/struct-types.go",
+ "@@ -1,9 +1,9 @@",
+ "-type s1 struct {}",
+ "-type s2 struct { Person }",
+ "-type s3 struct {",
+ "+type t1 struct {}",
+ "+type t2 struct { Person }",
+ "+type t3 struct {",
+ " f, g int",
+ " }",
+ "-type s4 struct {",
+ "+type t4 struct {",
+ " p.s1",
+ " h int `json:\"h\"`",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "9eaf4bcf83a325d326b7a80df99c64b1f2534fe2"
+ "shas": "2f9c7f7af1b13c6dae856277d12728846ad6b21b..c05ebbc06b206073de79e0a01191f0178cf1df71"
}
,{
"testCaseDescription": "go-struct-types-delete-replacement-test",
@@ -917,11 +997,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -932,11 +1012,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
18
]
}
@@ -947,11 +1027,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -962,11 +1042,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
18
],
"end": [
- 4,
+ 2,
24
]
}
@@ -977,11 +1057,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -992,11 +1072,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -1007,11 +1087,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -1022,11 +1102,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
9
]
}
@@ -1037,11 +1117,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
}
@@ -1052,11 +1132,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
2
]
}
@@ -1067,11 +1147,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
3
],
"end": [
- 9,
+ 7,
5
]
}
@@ -1082,11 +1162,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
2
],
"end": [
- 10,
+ 8,
3
]
}
@@ -1097,11 +1177,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
4
],
"end": [
- 10,
+ 8,
7
]
}
@@ -1112,11 +1192,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
8
],
"end": [
- 10,
+ 8,
18
]
}
@@ -1127,11 +1207,11 @@
"span": {
"delete": {
"start": [
- 12,
+ 10,
6
],
"end": [
- 12,
+ 10,
8
]
}
@@ -1142,11 +1222,11 @@
"span": {
"delete": {
"start": [
- 12,
+ 10,
9
],
"end": [
- 12,
+ 10,
18
]
}
@@ -1157,11 +1237,11 @@
"span": {
"delete": {
"start": [
- 13,
+ 11,
6
],
"end": [
- 13,
+ 11,
8
]
}
@@ -1172,11 +1252,11 @@
"span": {
"delete": {
"start": [
- 13,
+ 11,
18
],
"end": [
- 13,
+ 11,
24
]
}
@@ -1187,11 +1267,11 @@
"span": {
"delete": {
"start": [
- 14,
+ 12,
6
],
"end": [
- 14,
+ 12,
8
]
}
@@ -1202,11 +1282,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
1
],
"end": [
- 15,
+ 13,
2
]
}
@@ -1217,11 +1297,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
4
],
"end": [
- 15,
+ 13,
5
]
}
@@ -1232,11 +1312,11 @@
"span": {
"delete": {
"start": [
- 15,
+ 13,
6
],
"end": [
- 15,
+ 13,
9
]
}
@@ -1247,11 +1327,11 @@
"span": {
"delete": {
"start": [
- 17,
+ 15,
6
],
"end": [
- 17,
+ 15,
8
]
}
@@ -1262,11 +1342,11 @@
"span": {
"delete": {
"start": [
- 18,
+ 16,
1
],
"end": [
- 18,
+ 16,
2
]
}
@@ -1277,11 +1357,11 @@
"span": {
"delete": {
"start": [
- 18,
+ 16,
3
],
"end": [
- 18,
+ 16,
5
]
}
@@ -1292,11 +1372,11 @@
"span": {
"delete": {
"start": [
- 19,
+ 17,
2
],
"end": [
- 19,
+ 17,
3
]
}
@@ -1307,11 +1387,11 @@
"span": {
"delete": {
"start": [
- 19,
+ 17,
4
],
"end": [
- 19,
+ 17,
7
]
}
@@ -1322,11 +1402,11 @@
"span": {
"delete": {
"start": [
- 19,
+ 17,
8
],
"end": [
- 19,
+ 17,
18
]
}
@@ -1337,11 +1417,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
6
],
"end": [
- 12,
+ 10,
8
]
}
@@ -1352,11 +1432,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
9
],
"end": [
- 12,
+ 10,
18
]
}
@@ -1367,11 +1447,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 11,
6
],
"end": [
- 13,
+ 11,
8
]
}
@@ -1382,11 +1462,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 11,
18
],
"end": [
- 13,
+ 11,
24
]
}
@@ -1397,11 +1477,11 @@
"span": {
"insert": {
"start": [
- 14,
+ 12,
6
],
"end": [
- 14,
+ 12,
8
]
}
@@ -1412,11 +1492,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
1
],
"end": [
- 15,
+ 13,
2
]
}
@@ -1427,11 +1507,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
4
],
"end": [
- 15,
+ 13,
5
]
}
@@ -1442,11 +1522,11 @@
"span": {
"insert": {
"start": [
- 15,
+ 13,
6
],
"end": [
- 15,
+ 13,
9
]
}
@@ -1457,11 +1537,11 @@
"span": {
"insert": {
"start": [
- 17,
+ 15,
6
],
"end": [
- 17,
+ 15,
8
]
}
@@ -1472,11 +1552,11 @@
"span": {
"insert": {
"start": [
- 18,
+ 16,
1
],
"end": [
- 18,
+ 16,
2
]
}
@@ -1487,11 +1567,11 @@
"span": {
"insert": {
"start": [
- 18,
+ 16,
3
],
"end": [
- 18,
+ 16,
5
]
}
@@ -1502,11 +1582,11 @@
"span": {
"insert": {
"start": [
- 19,
+ 17,
2
],
"end": [
- 19,
+ 17,
3
]
}
@@ -1517,11 +1597,11 @@
"span": {
"insert": {
"start": [
- 19,
+ 17,
4
],
"end": [
- 19,
+ 17,
7
]
}
@@ -1532,11 +1612,11 @@
"span": {
"insert": {
"start": [
- 19,
+ 17,
8
],
"end": [
- 19,
+ 17,
18
]
}
@@ -1550,9 +1630,44 @@
"filePaths": [
"struct-types.go"
],
- "sha1": "9eaf4bcf83a325d326b7a80df99c64b1f2534fe2",
+ "patch": [
+ "diff --git a/struct-types.go b/struct-types.go",
+ "index e1f6f1a..c0626ed 100644",
+ "--- a/struct-types.go",
+ "+++ b/struct-types.go",
+ "@@ -1,12 +1,3 @@",
+ "-type t1 struct {}",
+ "-type t2 struct { Person }",
+ "-type t3 struct {",
+ "-f, g int",
+ "-}",
+ "-type t4 struct {",
+ "-p.s1",
+ "- h int `json:\"h\"`",
+ "-}",
+ " type s1 struct {}",
+ " type s2 struct { Person }",
+ " type s3 struct {",
+ "@@ -16,12 +7,12 @@ type s4 struct {",
+ " p.s1",
+ " h int `json:\"h\"`",
+ " }",
+ "-type s1 struct {}",
+ "-type s2 struct { Person }",
+ "-type s3 struct {",
+ "+type t1 struct {}",
+ "+type t2 struct { Person }",
+ "+type t3 struct {",
+ " f, g int",
+ " }",
+ "-type s4 struct {",
+ "+type t4 struct {",
+ " p.s1",
+ " h int `json:\"h\"`",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "8ad8fc0e8972d1a745999a3ff410e2d9917c6c1a"
+ "shas": "c05ebbc06b206073de79e0a01191f0178cf1df71..46308bfbaae7b526d57e38f6f85cd320c26bf5ac"
}
,{
"testCaseDescription": "go-struct-types-delete-test",
@@ -1563,11 +1678,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -1578,11 +1693,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
18
]
}
@@ -1593,11 +1708,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -1608,11 +1723,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
18
],
"end": [
- 4,
+ 2,
24
]
}
@@ -1623,11 +1738,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -1638,11 +1753,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -1653,11 +1768,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -1668,11 +1783,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
9
]
}
@@ -1683,11 +1798,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
}
@@ -1698,11 +1813,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
2
]
}
@@ -1713,11 +1828,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
3
],
"end": [
- 9,
+ 7,
5
]
}
@@ -1728,11 +1843,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
2
],
"end": [
- 10,
+ 8,
3
]
}
@@ -1743,11 +1858,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
4
],
"end": [
- 10,
+ 8,
7
]
}
@@ -1758,11 +1873,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
8
],
"end": [
- 10,
+ 8,
18
]
}
@@ -1776,9 +1891,27 @@
"filePaths": [
"struct-types.go"
],
- "sha1": "8ad8fc0e8972d1a745999a3ff410e2d9917c6c1a",
+ "patch": [
+ "diff --git a/struct-types.go b/struct-types.go",
+ "index c0626ed..f5a8d63 100644",
+ "--- a/struct-types.go",
+ "+++ b/struct-types.go",
+ "@@ -1,12 +1,3 @@",
+ "-type s1 struct {}",
+ "-type s2 struct { Person }",
+ "-type s3 struct {",
+ "-f, g int",
+ "-}",
+ "-type s4 struct {",
+ "-p.s1",
+ "- h int `json:\"h\"`",
+ "-}",
+ " type t1 struct {}",
+ " type t2 struct { Person }",
+ " type t3 struct {"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "a83a48a28e1242a55fbd63865d951b805a2885ab"
+ "shas": "46308bfbaae7b526d57e38f6f85cd320c26bf5ac..1f5b714b130069d9d1b8158abae029d0c826a4da"
}
,{
"testCaseDescription": "go-struct-types-delete-rest-test",
@@ -1789,11 +1922,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
@@ -1804,11 +1937,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
18
]
}
@@ -1819,11 +1952,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
@@ -1834,11 +1967,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
18
],
"end": [
- 4,
+ 2,
24
]
}
@@ -1849,11 +1982,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
@@ -1864,11 +1997,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
2
]
}
@@ -1879,11 +2012,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -1894,11 +2027,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
6
],
"end": [
- 6,
+ 4,
9
]
}
@@ -1909,11 +2042,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
8
]
}
@@ -1924,11 +2057,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
1
],
"end": [
- 9,
+ 7,
2
]
}
@@ -1939,11 +2072,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
3
],
"end": [
- 9,
+ 7,
5
]
}
@@ -1954,11 +2087,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
2
],
"end": [
- 10,
+ 8,
3
]
}
@@ -1969,11 +2102,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
4
],
"end": [
- 10,
+ 8,
7
]
}
@@ -1984,11 +2117,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
8
],
"end": [
- 10,
+ 8,
18
]
}
@@ -2002,7 +2135,22 @@
"filePaths": [
"struct-types.go"
],
- "sha1": "a83a48a28e1242a55fbd63865d951b805a2885ab",
+ "patch": [
+ "diff --git a/struct-types.go b/struct-types.go",
+ "index f5a8d63..e69de29 100644",
+ "--- a/struct-types.go",
+ "+++ b/struct-types.go",
+ "@@ -1,9 +0,0 @@",
+ "-type t1 struct {}",
+ "-type t2 struct { Person }",
+ "-type t3 struct {",
+ "-f, g int",
+ "-}",
+ "-type t4 struct {",
+ "-p.s1",
+ "- h int `json:\"h\"`",
+ "-}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "728019c0b896205942333966d15ec7058abf5edd"
+ "shas": "1f5b714b130069d9d1b8158abae029d0c826a4da..68a6be5450d3faa920cd8148a582aacf50d05b22"
}]
diff --git a/test/corpus/diff-summaries/go/switch-statements.json b/test/corpus/diff-summaries/go/switch-statements.json
index 6040e28cd..6565c997e 100644
--- a/test/corpus/diff-summaries/go/switch-statements.json
+++ b/test/corpus/diff-summaries/go/switch-statements.json
@@ -7,136 +7,16 @@
"span": {
"insert": {
"start": [
- 3,
- 15
- ],
- "end": [
- 3,
- 16
- ]
- }
- },
- "summary": "Added the 'x' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 3,
- 19
- ],
- "end": [
- 3,
- 20
- ]
- }
- },
- "summary": "Added the 'y' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 3,
- 22
- ],
- "end": [
- 3,
- 26
- ]
- }
- },
- "summary": "Added the 'f1()' function call"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 6
+ 1,
+ 1
],
"end": [
4,
- 7
+ 2
]
}
},
- "summary": "Added the 'x' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 10
- ],
- "end": [
- 4,
- 11
- ]
- }
- },
- "summary": "Added the 'z' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 13
- ],
- "end": [
- 4,
- 16
- ]
- }
- },
- "summary": "Added the 'g()' function call"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 7
- ]
- }
- },
- "summary": "Added the 'x' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 11
- ],
- "end": [
- 5,
- 12
- ]
- }
- },
- "summary": "Added the '4'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 14
- ],
- "end": [
- 5,
- 17
- ]
- }
- },
- "summary": "Added the 'h()' function call"
+ "summary": "Added the 'branch' switch statement"
}
]
},
@@ -145,9 +25,19 @@
"filePaths": [
"switch-statements.go"
],
- "sha1": "ad009ae663a027f35bb25867c4aa1375820fd816",
+ "patch": [
+ "diff --git a/switch-statements.go b/switch-statements.go",
+ "index e69de29..e444d1e 100644",
+ "--- a/switch-statements.go",
+ "+++ b/switch-statements.go",
+ "@@ -0,0 +1,4 @@",
+ "+switch { case x < y: f1()",
+ "+case x < z: g()",
+ "+case x == 4: h()",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "eca256b2b008a62971c928a2009d22eadc8b1bf4"
+ "shas": "c8c183bd98d018d2097fe1ee036d32d979f4919b..020bc6edfc32fb9f861efb86b1235abee8e48b24"
}
,{
"testCaseDescription": "go-switch-statements-replacement-insert-test",
@@ -156,30 +46,33 @@
"switch-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 7,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'branch' switch statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 8,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'branch' switch statement"
}
]
},
@@ -188,9 +81,26 @@
"filePaths": [
"switch-statements.go"
],
- "sha1": "eca256b2b008a62971c928a2009d22eadc8b1bf4",
+ "patch": [
+ "diff --git a/switch-statements.go b/switch-statements.go",
+ "index e444d1e..e2e5cf3 100644",
+ "--- a/switch-statements.go",
+ "+++ b/switch-statements.go",
+ "@@ -1,3 +1,11 @@",
+ "+switch { case a < b: f1()",
+ "+case c < d: g()",
+ "+case e == 4: f()",
+ "+}",
+ "+switch { case x < y: f1()",
+ "+case x < z: g()",
+ "+case x == 4: h()",
+ "+}",
+ " switch { case x < y: f1()",
+ " case x < z: g()",
+ " case x == 4: h()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "6cf706b5feaf6184c5678978e67906307f7e57ef"
+ "shas": "020bc6edfc32fb9f861efb86b1235abee8e48b24..04b985509e45dfad338288f50a012917d7c1cc65"
}
,{
"testCaseDescription": "go-switch-statements-delete-insert-test",
@@ -202,156 +112,156 @@
"replace": [
{
"start": [
- 3,
+ 1,
15
],
"end": [
- 3,
+ 1,
16
]
},
{
"start": [
- 3,
+ 1,
15
],
"end": [
- 3,
+ 1,
16
]
}
]
},
- "summary": "Replaced the 'a' identifier with the 'x' identifier"
+ "summary": "Replaced the 'a' identifier with the 'x' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
19
],
"end": [
- 3,
+ 1,
20
]
},
{
"start": [
- 3,
+ 1,
19
],
"end": [
- 3,
+ 1,
20
]
}
]
},
- "summary": "Replaced the 'b' identifier with the 'y' identifier"
+ "summary": "Replaced the 'b' identifier with the 'y' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
]
},
- "summary": "Replaced the 'c' identifier with the 'x' identifier"
+ "summary": "Replaced the 'c' identifier with the 'x' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
},
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
]
},
- "summary": "Replaced the 'd' identifier with the 'z' identifier"
+ "summary": "Replaced the 'd' identifier with the 'z' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
]
},
- "summary": "Replaced the 'e' identifier with the 'x' identifier"
+ "summary": "Replaced the 'e' identifier with the 'x' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
14
],
"end": [
- 5,
+ 3,
15
]
},
{
"start": [
- 5,
+ 3,
14
],
"end": [
- 5,
+ 3,
15
]
}
@@ -366,9 +276,24 @@
"filePaths": [
"switch-statements.go"
],
- "sha1": "6cf706b5feaf6184c5678978e67906307f7e57ef",
+ "patch": [
+ "diff --git a/switch-statements.go b/switch-statements.go",
+ "index e2e5cf3..143707d 100644",
+ "--- a/switch-statements.go",
+ "+++ b/switch-statements.go",
+ "@@ -1,6 +1,6 @@",
+ "-switch { case a < b: f1()",
+ "-case c < d: g()",
+ "-case e == 4: f()",
+ "+switch { case x < y: f1()",
+ "+case x < z: g()",
+ "+case x == 4: h()",
+ " }",
+ " switch { case x < y: f1()",
+ " case x < z: g()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b989fd66b8f35311c6663707229199f3ece5caf1"
+ "shas": "04b985509e45dfad338288f50a012917d7c1cc65..512e9c011295b86f98fbb5365c3019681fb5ca63"
}
,{
"testCaseDescription": "go-switch-statements-replacement-test",
@@ -380,156 +305,156 @@
"replace": [
{
"start": [
- 3,
+ 1,
15
],
"end": [
- 3,
+ 1,
16
]
},
{
"start": [
- 3,
+ 1,
15
],
"end": [
- 3,
+ 1,
16
]
}
]
},
- "summary": "Replaced the 'x' identifier with the 'a' identifier"
+ "summary": "Replaced the 'x' identifier with the 'a' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
19
],
"end": [
- 3,
+ 1,
20
]
},
{
"start": [
- 3,
+ 1,
19
],
"end": [
- 3,
+ 1,
20
]
}
]
},
- "summary": "Replaced the 'y' identifier with the 'b' identifier"
+ "summary": "Replaced the 'y' identifier with the 'b' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
]
},
- "summary": "Replaced the 'x' identifier with the 'c' identifier"
+ "summary": "Replaced the 'x' identifier with the 'c' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
},
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
]
},
- "summary": "Replaced the 'z' identifier with the 'd' identifier"
+ "summary": "Replaced the 'z' identifier with the 'd' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
]
},
- "summary": "Replaced the 'x' identifier with the 'e' identifier"
+ "summary": "Replaced the 'x' identifier with the 'e' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
14
],
"end": [
- 5,
+ 3,
15
]
},
{
"start": [
- 5,
+ 3,
14
],
"end": [
- 5,
+ 3,
15
]
}
@@ -544,9 +469,24 @@
"filePaths": [
"switch-statements.go"
],
- "sha1": "b989fd66b8f35311c6663707229199f3ece5caf1",
+ "patch": [
+ "diff --git a/switch-statements.go b/switch-statements.go",
+ "index 143707d..e2e5cf3 100644",
+ "--- a/switch-statements.go",
+ "+++ b/switch-statements.go",
+ "@@ -1,6 +1,6 @@",
+ "-switch { case x < y: f1()",
+ "-case x < z: g()",
+ "-case x == 4: h()",
+ "+switch { case a < b: f1()",
+ "+case c < d: g()",
+ "+case e == 4: f()",
+ " }",
+ " switch { case x < y: f1()",
+ " case x < z: g()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "882983ce40cff6b060eabe22c2b8a9382fdb50c7"
+ "shas": "512e9c011295b86f98fbb5365c3019681fb5ca63..a2893f326cd63baa7745661ac248ed6c89a5b753"
}
,{
"testCaseDescription": "go-switch-statements-delete-replacement-test",
@@ -557,406 +497,46 @@
"span": {
"delete": {
"start": [
- 3,
- 15
- ],
- "end": [
- 3,
- 16
- ]
- }
- },
- "summary": "Deleted the 'a' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 19
- ],
- "end": [
- 3,
- 20
- ]
- }
- },
- "summary": "Deleted the 'b' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 22
- ],
- "end": [
- 3,
- 26
- ]
- }
- },
- "summary": "Deleted the 'f1()' function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 4,
- 6
+ 1,
+ 1
],
"end": [
4,
- 7
+ 2
]
}
},
- "summary": "Deleted the 'c' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 4,
- 10
- ],
- "end": [
- 4,
- 11
- ]
- }
- },
- "summary": "Deleted the 'd' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 4,
- 13
- ],
- "end": [
- 4,
- 16
- ]
- }
- },
- "summary": "Deleted the 'g()' function call"
+ "summary": "Deleted the 'branch' switch statement"
},
{
"span": {
"delete": {
"start": [
5,
- 6
+ 1
],
"end": [
- 5,
- 7
+ 8,
+ 2
]
}
},
- "summary": "Deleted the 'e' identifier"
+ "summary": "Deleted the 'branch' switch statement"
},
{
"span": {
- "delete": {
+ "insert": {
"start": [
5,
- 11
- ],
- "end": [
- 5,
- 12
- ]
- }
- },
- "summary": "Deleted the '4'"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 14
- ],
- "end": [
- 5,
- 17
- ]
- }
- },
- "summary": "Deleted the 'f()' function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 7,
- 15
- ],
- "end": [
- 7,
- 16
- ]
- }
- },
- "summary": "Deleted the 'x' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 7,
- 19
- ],
- "end": [
- 7,
- 20
- ]
- }
- },
- "summary": "Deleted the 'y' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 7,
- 22
- ],
- "end": [
- 7,
- 26
- ]
- }
- },
- "summary": "Deleted the 'f1()' function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 6
+ 1
],
"end": [
8,
- 7
+ 2
]
}
},
- "summary": "Deleted the 'x' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 10
- ],
- "end": [
- 8,
- 11
- ]
- }
- },
- "summary": "Deleted the 'z' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 13
- ],
- "end": [
- 8,
- 16
- ]
- }
- },
- "summary": "Deleted the 'g()' function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 9,
- 6
- ],
- "end": [
- 9,
- 7
- ]
- }
- },
- "summary": "Deleted the 'x' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 9,
- 11
- ],
- "end": [
- 9,
- 12
- ]
- }
- },
- "summary": "Deleted the '4'"
- },
- {
- "span": {
- "delete": {
- "start": [
- 9,
- 14
- ],
- "end": [
- 9,
- 17
- ]
- }
- },
- "summary": "Deleted the 'h()' function call"
- },
- {
- "span": {
- "insert": {
- "start": [
- 7,
- 15
- ],
- "end": [
- 7,
- 16
- ]
- }
- },
- "summary": "Added the 'a' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 7,
- 19
- ],
- "end": [
- 7,
- 20
- ]
- }
- },
- "summary": "Added the 'b' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 7,
- 22
- ],
- "end": [
- 7,
- 26
- ]
- }
- },
- "summary": "Added the 'f1()' function call"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 6
- ],
- "end": [
- 8,
- 7
- ]
- }
- },
- "summary": "Added the 'c' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 10
- ],
- "end": [
- 8,
- 11
- ]
- }
- },
- "summary": "Added the 'd' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 13
- ],
- "end": [
- 8,
- 16
- ]
- }
- },
- "summary": "Added the 'g()' function call"
- },
- {
- "span": {
- "insert": {
- "start": [
- 9,
- 6
- ],
- "end": [
- 9,
- 7
- ]
- }
- },
- "summary": "Added the 'e' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 9,
- 11
- ],
- "end": [
- 9,
- 12
- ]
- }
- },
- "summary": "Added the '4'"
- },
- {
- "span": {
- "insert": {
- "start": [
- 9,
- 14
- ],
- "end": [
- 9,
- 17
- ]
- }
- },
- "summary": "Added the 'f()' function call"
+ "summary": "Added the 'branch' switch statement"
}
]
},
@@ -965,9 +545,30 @@
"filePaths": [
"switch-statements.go"
],
- "sha1": "882983ce40cff6b060eabe22c2b8a9382fdb50c7",
+ "patch": [
+ "diff --git a/switch-statements.go b/switch-statements.go",
+ "index e2e5cf3..6989d28 100644",
+ "--- a/switch-statements.go",
+ "+++ b/switch-statements.go",
+ "@@ -1,12 +1,8 @@",
+ "-switch { case a < b: f1()",
+ "-case c < d: g()",
+ "-case e == 4: f()",
+ "-}",
+ " switch { case x < y: f1()",
+ " case x < z: g()",
+ " case x == 4: h()",
+ " }",
+ "-switch { case x < y: f1()",
+ "-case x < z: g()",
+ "-case x == 4: h()",
+ "+switch { case a < b: f1()",
+ "+case c < d: g()",
+ "+case e == 4: f()",
+ " }"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "25d10a5d7a4393580359323f5bc44091c8631f64"
+ "shas": "a2893f326cd63baa7745661ac248ed6c89a5b753..8fa269f6066d9af690e77c25a001676c1dd0006d"
}
,{
"testCaseDescription": "go-switch-statements-delete-test",
@@ -976,30 +577,18 @@
"switch-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 7,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'branch' switch statement"
}
]
},
@@ -1008,9 +597,22 @@
"filePaths": [
"switch-statements.go"
],
- "sha1": "25d10a5d7a4393580359323f5bc44091c8631f64",
+ "patch": [
+ "diff --git a/switch-statements.go b/switch-statements.go",
+ "index 6989d28..eff174f 100644",
+ "--- a/switch-statements.go",
+ "+++ b/switch-statements.go",
+ "@@ -1,7 +1,3 @@",
+ "-switch { case x < y: f1()",
+ "-case x < z: g()",
+ "-case x == 4: h()",
+ "-}",
+ " switch { case a < b: f1()",
+ " case c < d: g()",
+ " case e == 4: f()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "5a3c200ddcdc80be60f7cb691c69cfb4ca04349b"
+ "shas": "8fa269f6066d9af690e77c25a001676c1dd0006d..ea34f6abefdc955b234f63e478f97bb6656f82bd"
}
,{
"testCaseDescription": "go-switch-statements-delete-rest-test",
@@ -1021,136 +623,16 @@
"span": {
"delete": {
"start": [
- 3,
- 15
- ],
- "end": [
- 3,
- 16
- ]
- }
- },
- "summary": "Deleted the 'a' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 19
- ],
- "end": [
- 3,
- 20
- ]
- }
- },
- "summary": "Deleted the 'b' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 22
- ],
- "end": [
- 3,
- 26
- ]
- }
- },
- "summary": "Deleted the 'f1()' function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 4,
- 6
+ 1,
+ 1
],
"end": [
4,
- 7
+ 2
]
}
},
- "summary": "Deleted the 'c' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 4,
- 10
- ],
- "end": [
- 4,
- 11
- ]
- }
- },
- "summary": "Deleted the 'd' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 4,
- 13
- ],
- "end": [
- 4,
- 16
- ]
- }
- },
- "summary": "Deleted the 'g()' function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 7
- ]
- }
- },
- "summary": "Deleted the 'e' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 11
- ],
- "end": [
- 5,
- 12
- ]
- }
- },
- "summary": "Deleted the '4'"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 14
- ],
- "end": [
- 5,
- 17
- ]
- }
- },
- "summary": "Deleted the 'f()' function call"
+ "summary": "Deleted the 'branch' switch statement"
}
]
},
@@ -1159,7 +641,17 @@
"filePaths": [
"switch-statements.go"
],
- "sha1": "5a3c200ddcdc80be60f7cb691c69cfb4ca04349b",
+ "patch": [
+ "diff --git a/switch-statements.go b/switch-statements.go",
+ "index eff174f..e69de29 100644",
+ "--- a/switch-statements.go",
+ "+++ b/switch-statements.go",
+ "@@ -1,4 +0,0 @@",
+ "-switch { case a < b: f1()",
+ "-case c < d: g()",
+ "-case e == 4: f()",
+ "-}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "5ed5348fda2a0c23b658e6e2a4a918d6abfd9b09"
+ "shas": "ea34f6abefdc955b234f63e478f97bb6656f82bd..2de5024544064b228b54159d60307f986fdc8ee9"
}]
diff --git a/test/corpus/diff-summaries/go/type-assertion-expressions.json b/test/corpus/diff-summaries/go/type-assertion-expressions.json
index ae6aa936a..0bec49642 100644
--- a/test/corpus/diff-summaries/go/type-assertion-expressions.json
+++ b/test/corpus/diff-summaries/go/type-assertion-expressions.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
12
]
}
@@ -55,9 +55,16 @@
"filePaths": [
"type-assertion-expressions.go"
],
- "sha1": "b1669d02e282b6c97db8719b314b3fc45b149496",
+ "patch": [
+ "diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
+ "index e69de29..0765038 100644",
+ "--- a/type-assertion-expressions.go",
+ "+++ b/type-assertion-expressions.go",
+ "@@ -0,0 +1 @@",
+ "+x.(z.Person)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3eca1bc5dc05a442f328ece5d82eb5d668d0eaf7"
+ "shas": "d3f3af3265adb9413a11a3528b28667b0c70a1e2..7b6b8caa4b207c3c450f5e87744c58fb53baf8c3"
}
,{
"testCaseDescription": "go-type-assertion-expressions-replacement-insert-test",
@@ -66,30 +73,93 @@
"type-assertion-expressions.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 2
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 4
+ ],
+ "end": [
+ 1,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 6
+ ],
+ "end": [
+ 1,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the 'Dog' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'x' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 4
+ ],
+ "end": [
+ 2,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'z' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 6
+ ],
+ "end": [
+ 2,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'Person' identifier"
}
]
},
@@ -98,9 +168,18 @@
"filePaths": [
"type-assertion-expressions.go"
],
- "sha1": "3eca1bc5dc05a442f328ece5d82eb5d668d0eaf7",
+ "patch": [
+ "diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
+ "index 0765038..56239fb 100644",
+ "--- a/type-assertion-expressions.go",
+ "+++ b/type-assertion-expressions.go",
+ "@@ -1 +1,3 @@",
+ "+b.(c.Dog)",
+ "+x.(z.Person)",
+ " x.(z.Person)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "18d82c20e80e8c2616e2bee249c6469ed80caf66"
+ "shas": "7b6b8caa4b207c3c450f5e87744c58fb53baf8c3..114120738b787beac6725da990d63863e4e2905b"
}
,{
"testCaseDescription": "go-type-assertion-expressions-delete-insert-test",
@@ -112,21 +191,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -139,21 +218,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
},
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -166,21 +245,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
9
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
12
]
}
@@ -195,9 +274,19 @@
"filePaths": [
"type-assertion-expressions.go"
],
- "sha1": "18d82c20e80e8c2616e2bee249c6469ed80caf66",
+ "patch": [
+ "diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
+ "index 56239fb..de94018 100644",
+ "--- a/type-assertion-expressions.go",
+ "+++ b/type-assertion-expressions.go",
+ "@@ -1,3 +1,3 @@",
+ "-b.(c.Dog)",
+ "+x.(z.Person)",
+ " x.(z.Person)",
+ " x.(z.Person)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f7f61458523524f9156c118a842acae8684a9fb8"
+ "shas": "114120738b787beac6725da990d63863e4e2905b..d01aada8630c1fa14c98e7c4344c6f91d0555e98"
}
,{
"testCaseDescription": "go-type-assertion-expressions-replacement-test",
@@ -209,21 +298,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
},
{
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -236,21 +325,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
},
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -263,21 +352,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
12
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
9
]
}
@@ -292,9 +381,19 @@
"filePaths": [
"type-assertion-expressions.go"
],
- "sha1": "f7f61458523524f9156c118a842acae8684a9fb8",
+ "patch": [
+ "diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
+ "index de94018..56239fb 100644",
+ "--- a/type-assertion-expressions.go",
+ "+++ b/type-assertion-expressions.go",
+ "@@ -1,3 +1,3 @@",
+ "-x.(z.Person)",
+ "+b.(c.Dog)",
+ " x.(z.Person)",
+ " x.(z.Person)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "eb4314e57e567795e18580f8bad6174d71f6079e"
+ "shas": "d01aada8630c1fa14c98e7c4344c6f91d0555e98..123e6af58b082c4fb361e05c141910b0e258c557"
}
,{
"testCaseDescription": "go-type-assertion-expressions-delete-replacement-test",
@@ -305,11 +404,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -320,11 +419,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -335,11 +434,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
9
]
}
@@ -350,11 +449,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -365,11 +464,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
4
],
"end": [
- 4,
+ 2,
5
]
}
@@ -380,11 +479,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
12
]
}
@@ -395,11 +494,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
2
]
}
@@ -410,11 +509,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
4
],
"end": [
- 4,
+ 2,
5
]
}
@@ -425,11 +524,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
9
]
}
@@ -443,9 +542,19 @@
"filePaths": [
"type-assertion-expressions.go"
],
- "sha1": "eb4314e57e567795e18580f8bad6174d71f6079e",
+ "patch": [
+ "diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
+ "index 56239fb..aa7c34c 100644",
+ "--- a/type-assertion-expressions.go",
+ "+++ b/type-assertion-expressions.go",
+ "@@ -1,3 +1,2 @@",
+ "-b.(c.Dog)",
+ "-x.(z.Person)",
+ " x.(z.Person)",
+ "+b.(c.Dog)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "0ce99c947903940b17396384f338c33a5ea5dbc7"
+ "shas": "123e6af58b082c4fb361e05c141910b0e258c557..986aa572f724e252f2bd33b8f1930f46b2b1314a"
}
,{
"testCaseDescription": "go-type-assertion-expressions-delete-test",
@@ -454,30 +563,48 @@
"type-assertion-expressions.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 2
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'x' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 4
+ ],
+ "end": [
+ 1,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'z' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 6
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the 'Person' identifier"
}
]
},
@@ -486,9 +613,17 @@
"filePaths": [
"type-assertion-expressions.go"
],
- "sha1": "0ce99c947903940b17396384f338c33a5ea5dbc7",
+ "patch": [
+ "diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
+ "index aa7c34c..093a081 100644",
+ "--- a/type-assertion-expressions.go",
+ "+++ b/type-assertion-expressions.go",
+ "@@ -1,2 +1 @@",
+ "-x.(z.Person)",
+ " b.(c.Dog)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "54efa88da5245a5bd75fa463c4f286849d0ce1b7"
+ "shas": "986aa572f724e252f2bd33b8f1930f46b2b1314a..3e70ca6b1cd1883b8495832c3e57983edabf55b1"
}
,{
"testCaseDescription": "go-type-assertion-expressions-delete-rest-test",
@@ -499,11 +634,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
2
]
}
@@ -514,11 +649,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -529,11 +664,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
9
]
}
@@ -547,7 +682,14 @@
"filePaths": [
"type-assertion-expressions.go"
],
- "sha1": "54efa88da5245a5bd75fa463c4f286849d0ce1b7",
+ "patch": [
+ "diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
+ "index 093a081..e69de29 100644",
+ "--- a/type-assertion-expressions.go",
+ "+++ b/type-assertion-expressions.go",
+ "@@ -1 +0,0 @@",
+ "-b.(c.Dog)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ac77956a23a92cbf0da1aa714b566fb94d240162"
+ "shas": "3e70ca6b1cd1883b8495832c3e57983edabf55b1..693cdf76f21d015a636d4ac6c87f795ed6bd090b"
}]
diff --git a/test/corpus/diff-summaries/go/type-conversion-expressions.json b/test/corpus/diff-summaries/go/type-conversion-expressions.json
index 90ccf0d21..569b935e4 100644
--- a/test/corpus/diff-summaries/go/type-conversion-expressions.json
+++ b/test/corpus/diff-summaries/go/type-conversion-expressions.json
@@ -5,30 +5,213 @@
"type-conversion-expressions.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 3
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 9
+ ],
+ "end": [
+ 1,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'd' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 7
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 10
+ ],
+ "end": [
+ 2,
+ 11
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the 'd' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 2
+ ],
+ "end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'e' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 4
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'f' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 6
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ }
+ },
+ "summary": "Added the 'g' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'e' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 5
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'f' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 8
+ ],
+ "end": [
+ 4,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the 'g' identifier"
}
]
},
@@ -37,9 +220,19 @@
"filePaths": [
"type-conversion-expressions.go"
],
- "sha1": "ac77956a23a92cbf0da1aa714b566fb94d240162",
+ "patch": [
+ "diff --git a/type-conversion-expressions.go b/type-conversion-expressions.go",
+ "index e69de29..9bf5745 100644",
+ "--- a/type-conversion-expressions.go",
+ "+++ b/type-conversion-expressions.go",
+ "@@ -0,0 +1,4 @@",
+ "+[]a.b(c.d)",
+ "+ ([]a.b)(c.d)",
+ "+ e.f(g)",
+ "+ (e.f)(g)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7c6e2b5a1240b0eaee7c3f01f6bc80c8e6ba0bf3"
+ "shas": "693cdf76f21d015a636d4ac6c87f795ed6bd090b..951eedd74b99b815ce977d5424bd1724f8878007"
}
,{
"testCaseDescription": "go-type-conversion-expressions-replacement-insert-test",
@@ -50,11 +243,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -65,11 +258,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
}
@@ -80,11 +273,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
8
]
}
@@ -95,11 +288,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -110,11 +303,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
}
@@ -125,11 +318,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
7
],
"end": [
- 4,
+ 2,
8
]
}
@@ -140,11 +333,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -155,11 +348,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
}
@@ -170,11 +363,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -185,11 +378,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -200,11 +393,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
@@ -215,11 +408,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
3
],
"end": [
- 6,
+ 4,
4
]
}
@@ -230,11 +423,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
5
],
"end": [
- 6,
+ 4,
6
]
}
@@ -245,11 +438,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
}
@@ -260,11 +453,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
3
],
"end": [
- 7,
+ 5,
4
]
}
@@ -275,11 +468,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
6
]
}
@@ -290,11 +483,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
7
],
"end": [
- 7,
+ 5,
8
]
}
@@ -305,11 +498,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
9
],
"end": [
- 7,
+ 5,
10
]
}
@@ -320,11 +513,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
5
],
"end": [
- 8,
+ 6,
6
]
}
@@ -335,11 +528,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
7
],
"end": [
- 8,
+ 6,
8
]
}
@@ -350,11 +543,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
10
],
"end": [
- 8,
+ 6,
11
]
}
@@ -365,11 +558,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
12
],
"end": [
- 8,
+ 6,
13
]
}
@@ -380,11 +573,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
2
],
"end": [
- 9,
+ 7,
3
]
}
@@ -395,11 +588,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
4
],
"end": [
- 9,
+ 7,
5
]
}
@@ -410,11 +603,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
7
]
}
@@ -425,11 +618,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
3
],
"end": [
- 10,
+ 8,
4
]
}
@@ -440,11 +633,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
5
],
"end": [
- 10,
+ 8,
6
]
}
@@ -455,11 +648,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
8
],
"end": [
- 10,
+ 8,
9
]
}
@@ -473,9 +666,26 @@
"filePaths": [
"type-conversion-expressions.go"
],
- "sha1": "7c6e2b5a1240b0eaee7c3f01f6bc80c8e6ba0bf3",
+ "patch": [
+ "diff --git a/type-conversion-expressions.go b/type-conversion-expressions.go",
+ "index 9bf5745..f32ac9a 100644",
+ "--- a/type-conversion-expressions.go",
+ "+++ b/type-conversion-expressions.go",
+ "@@ -1,3 +1,11 @@",
+ "+[]x.y(z.e)",
+ "+ ([]f.g)(h.i)",
+ "+ j.k(l)",
+ "+ (m.n)(o)",
+ "+[]a.b(c.d)",
+ "+ ([]a.b)(c.d)",
+ "+ e.f(g)",
+ "+ (e.f)(g)",
+ " []a.b(c.d)",
+ " ([]a.b)(c.d)",
+ " e.f(g)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "72bf50176db02667805f05a367e621962651365d"
+ "shas": "951eedd74b99b815ce977d5424bd1724f8878007..fe9921554d8e947076152fc8ff33c781fa9d6904"
}
,{
"testCaseDescription": "go-type-conversion-expressions-delete-insert-test",
@@ -487,21 +697,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
},
{
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -514,21 +724,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
},
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
}
@@ -541,21 +751,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
8
]
}
@@ -568,21 +778,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
},
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -595,21 +805,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
},
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
}
@@ -622,21 +832,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
7
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
7
],
"end": [
- 4,
+ 2,
8
]
}
@@ -649,21 +859,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
},
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -676,21 +886,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
},
{
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
}
@@ -703,21 +913,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
},
{
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -730,21 +940,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
},
{
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -757,21 +967,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
@@ -784,21 +994,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
3
],
"end": [
- 6,
+ 4,
4
]
},
{
"start": [
- 6,
+ 4,
3
],
"end": [
- 6,
+ 4,
4
]
}
@@ -811,21 +1021,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
5
],
"end": [
- 6,
+ 4,
6
]
},
{
"start": [
- 6,
+ 4,
5
],
"end": [
- 6,
+ 4,
6
]
}
@@ -838,21 +1048,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
},
{
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
}
@@ -867,9 +1077,26 @@
"filePaths": [
"type-conversion-expressions.go"
],
- "sha1": "72bf50176db02667805f05a367e621962651365d",
+ "patch": [
+ "diff --git a/type-conversion-expressions.go b/type-conversion-expressions.go",
+ "index f32ac9a..3104653 100644",
+ "--- a/type-conversion-expressions.go",
+ "+++ b/type-conversion-expressions.go",
+ "@@ -1,7 +1,7 @@",
+ "-[]x.y(z.e)",
+ "- ([]f.g)(h.i)",
+ "- j.k(l)",
+ "- (m.n)(o)",
+ "+[]a.b(c.d)",
+ "+ ([]a.b)(c.d)",
+ "+ e.f(g)",
+ "+ (e.f)(g)",
+ " []a.b(c.d)",
+ " ([]a.b)(c.d)",
+ " e.f(g)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ef88dbc913c8d38a7ddccb4cc686d390cb5ac305"
+ "shas": "fe9921554d8e947076152fc8ff33c781fa9d6904..c18ac9b4916c5cbc6deed07cae52f5986ce9a263"
}
,{
"testCaseDescription": "go-type-conversion-expressions-replacement-test",
@@ -881,21 +1108,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
},
{
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -908,21 +1135,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
},
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
}
@@ -935,21 +1162,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
8
]
}
@@ -962,21 +1189,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
},
{
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -989,21 +1216,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
},
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
}
@@ -1016,21 +1243,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
7
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
7
],
"end": [
- 4,
+ 2,
8
]
}
@@ -1043,21 +1270,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
},
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -1070,21 +1297,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
},
{
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
}
@@ -1097,21 +1324,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
},
{
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -1124,21 +1351,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
},
{
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -1151,21 +1378,21 @@
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
@@ -1178,21 +1405,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
3
],
"end": [
- 6,
+ 4,
4
]
},
{
"start": [
- 6,
+ 4,
3
],
"end": [
- 6,
+ 4,
4
]
}
@@ -1205,21 +1432,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
5
],
"end": [
- 6,
+ 4,
6
]
},
{
"start": [
- 6,
+ 4,
5
],
"end": [
- 6,
+ 4,
6
]
}
@@ -1232,21 +1459,21 @@
"replace": [
{
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
},
{
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
}
@@ -1261,9 +1488,26 @@
"filePaths": [
"type-conversion-expressions.go"
],
- "sha1": "ef88dbc913c8d38a7ddccb4cc686d390cb5ac305",
+ "patch": [
+ "diff --git a/type-conversion-expressions.go b/type-conversion-expressions.go",
+ "index 3104653..f32ac9a 100644",
+ "--- a/type-conversion-expressions.go",
+ "+++ b/type-conversion-expressions.go",
+ "@@ -1,7 +1,7 @@",
+ "-[]a.b(c.d)",
+ "- ([]a.b)(c.d)",
+ "- e.f(g)",
+ "- (e.f)(g)",
+ "+[]x.y(z.e)",
+ "+ ([]f.g)(h.i)",
+ "+ j.k(l)",
+ "+ (m.n)(o)",
+ " []a.b(c.d)",
+ " ([]a.b)(c.d)",
+ " e.f(g)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3d0e28e4d214823dd642f139ad6c980f75ae74df"
+ "shas": "c18ac9b4916c5cbc6deed07cae52f5986ce9a263..186bae1d83ffbd7e2237ce1fa5fdbd86ddbcbb76"
}
,{
"testCaseDescription": "go-type-conversion-expressions-delete-replacement-test",
@@ -1274,11 +1518,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -1289,11 +1533,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
}
@@ -1304,11 +1548,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
8
]
}
@@ -1319,11 +1563,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -1334,11 +1578,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
}
@@ -1349,11 +1593,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
7
],
"end": [
- 4,
+ 2,
8
]
}
@@ -1364,11 +1608,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -1379,11 +1623,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
}
@@ -1394,11 +1638,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -1409,11 +1653,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -1424,11 +1668,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
@@ -1439,11 +1683,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
3
],
"end": [
- 6,
+ 4,
4
]
}
@@ -1454,11 +1698,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
5
],
"end": [
- 6,
+ 4,
6
]
}
@@ -1469,11 +1713,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
}
@@ -1484,11 +1728,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
3
],
"end": [
- 7,
+ 5,
4
]
}
@@ -1499,11 +1743,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
6
]
}
@@ -1514,11 +1758,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
7
],
"end": [
- 7,
+ 5,
8
]
}
@@ -1529,11 +1773,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
9
],
"end": [
- 7,
+ 5,
10
]
}
@@ -1544,11 +1788,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
5
],
"end": [
- 8,
+ 6,
6
]
}
@@ -1559,11 +1803,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
7
],
"end": [
- 8,
+ 6,
8
]
}
@@ -1574,11 +1818,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
10
],
"end": [
- 8,
+ 6,
11
]
}
@@ -1589,11 +1833,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
12
],
"end": [
- 8,
+ 6,
13
]
}
@@ -1604,11 +1848,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
2
],
"end": [
- 9,
+ 7,
3
]
}
@@ -1619,11 +1863,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
4
],
"end": [
- 9,
+ 7,
5
]
}
@@ -1634,11 +1878,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
7
]
}
@@ -1649,11 +1893,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
3
],
"end": [
- 10,
+ 8,
4
]
}
@@ -1664,11 +1908,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
5
],
"end": [
- 10,
+ 8,
6
]
}
@@ -1679,11 +1923,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
8
],
"end": [
- 10,
+ 8,
9
]
}
@@ -1694,11 +1938,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
3
],
"end": [
- 7,
+ 5,
4
]
}
@@ -1709,11 +1953,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
6
]
}
@@ -1724,11 +1968,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
7
],
"end": [
- 7,
+ 5,
8
]
}
@@ -1739,11 +1983,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
9
],
"end": [
- 7,
+ 5,
10
]
}
@@ -1754,11 +1998,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
5
],
"end": [
- 8,
+ 6,
6
]
}
@@ -1769,11 +2013,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
7
],
"end": [
- 8,
+ 6,
8
]
}
@@ -1784,11 +2028,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
10
],
"end": [
- 8,
+ 6,
11
]
}
@@ -1799,11 +2043,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
12
],
"end": [
- 8,
+ 6,
13
]
}
@@ -1814,11 +2058,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
2
],
"end": [
- 9,
+ 7,
3
]
}
@@ -1829,11 +2073,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
4
],
"end": [
- 9,
+ 7,
5
]
}
@@ -1844,11 +2088,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
6
],
"end": [
- 9,
+ 7,
7
]
}
@@ -1859,11 +2103,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
3
],
"end": [
- 10,
+ 8,
4
]
}
@@ -1874,11 +2118,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
5
],
"end": [
- 10,
+ 8,
6
]
}
@@ -1889,11 +2133,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
8
],
"end": [
- 10,
+ 8,
9
]
}
@@ -1907,9 +2151,31 @@
"filePaths": [
"type-conversion-expressions.go"
],
- "sha1": "3d0e28e4d214823dd642f139ad6c980f75ae74df",
+ "patch": [
+ "diff --git a/type-conversion-expressions.go b/type-conversion-expressions.go",
+ "index f32ac9a..91844af 100644",
+ "--- a/type-conversion-expressions.go",
+ "+++ b/type-conversion-expressions.go",
+ "@@ -1,12 +1,8 @@",
+ "-[]x.y(z.e)",
+ "- ([]f.g)(h.i)",
+ "- j.k(l)",
+ "- (m.n)(o)",
+ "-[]a.b(c.d)",
+ "- ([]a.b)(c.d)",
+ "- e.f(g)",
+ "- (e.f)(g)",
+ " []a.b(c.d)",
+ " ([]a.b)(c.d)",
+ " e.f(g)",
+ " (e.f)(g)",
+ "+[]x.y(z.e)",
+ "+ ([]f.g)(h.i)",
+ "+ j.k(l)",
+ "+ (m.n)(o)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "56fa1161d09ab982dd57f0a4f354ecec1d87e0bf"
+ "shas": "186bae1d83ffbd7e2237ce1fa5fdbd86ddbcbb76..4c040499e36c23860cc5768675842ae9943bd7de"
}
,{
"testCaseDescription": "go-type-conversion-expressions-delete-test",
@@ -1920,11 +2186,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
3
],
"end": [
- 3,
+ 1,
4
]
}
@@ -1935,11 +2201,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
}
@@ -1950,11 +2216,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
8
]
}
@@ -1965,11 +2231,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -1980,11 +2246,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
}
@@ -1995,11 +2261,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
7
],
"end": [
- 4,
+ 2,
8
]
}
@@ -2010,11 +2276,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
11
]
}
@@ -2025,11 +2291,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
12
],
"end": [
- 4,
+ 2,
13
]
}
@@ -2040,11 +2306,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -2055,11 +2321,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -2070,11 +2336,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
7
]
}
@@ -2085,11 +2351,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
3
],
"end": [
- 6,
+ 4,
4
]
}
@@ -2100,11 +2366,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
5
],
"end": [
- 6,
+ 4,
6
]
}
@@ -2115,11 +2381,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
8
],
"end": [
- 6,
+ 4,
9
]
}
@@ -2133,9 +2399,22 @@
"filePaths": [
"type-conversion-expressions.go"
],
- "sha1": "56fa1161d09ab982dd57f0a4f354ecec1d87e0bf",
+ "patch": [
+ "diff --git a/type-conversion-expressions.go b/type-conversion-expressions.go",
+ "index 91844af..7f172bc 100644",
+ "--- a/type-conversion-expressions.go",
+ "+++ b/type-conversion-expressions.go",
+ "@@ -1,7 +1,3 @@",
+ "-[]a.b(c.d)",
+ "- ([]a.b)(c.d)",
+ "- e.f(g)",
+ "- (e.f)(g)",
+ " []x.y(z.e)",
+ " ([]f.g)(h.i)",
+ " j.k(l)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "4952b1c56543c78e0c025c081b0dcc5fa8181f86"
+ "shas": "4c040499e36c23860cc5768675842ae9943bd7de..bb7df64dbe7318920e43066762d44b0ab4b8b559"
}
,{
"testCaseDescription": "go-type-conversion-expressions-delete-rest-test",
@@ -2144,30 +2423,213 @@
"type-conversion-expressions.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 3
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'x' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'y' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'z' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 9
+ ],
+ "end": [
+ 1,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted the 'e' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 5
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'f' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 7
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'g' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 10
+ ],
+ "end": [
+ 2,
+ 11
+ ]
+ }
+ },
+ "summary": "Deleted the 'h' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 12
+ ],
+ "end": [
+ 2,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'i' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 2
+ ],
+ "end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'j' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 4
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'k' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 6
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted the 'l' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'm' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 5
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'n' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 8
+ ],
+ "end": [
+ 4,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'o' identifier"
}
]
},
@@ -2176,7 +2638,17 @@
"filePaths": [
"type-conversion-expressions.go"
],
- "sha1": "4952b1c56543c78e0c025c081b0dcc5fa8181f86",
+ "patch": [
+ "diff --git a/type-conversion-expressions.go b/type-conversion-expressions.go",
+ "index 7f172bc..e69de29 100644",
+ "--- a/type-conversion-expressions.go",
+ "+++ b/type-conversion-expressions.go",
+ "@@ -1,4 +0,0 @@",
+ "-[]x.y(z.e)",
+ "- ([]f.g)(h.i)",
+ "- j.k(l)",
+ "- (m.n)(o)"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "423c95c361986c8807246777d0d1f5dd0602c5d7"
+ "shas": "bb7df64dbe7318920e43066762d44b0ab4b8b559..42975c2ba57995b8cc4cfe30c7599c673970dd25"
}]
diff --git a/test/corpus/diff-summaries/go/type-declarations.json b/test/corpus/diff-summaries/go/type-declarations.json
index 7c01edd90..d195e09c9 100644
--- a/test/corpus/diff-summaries/go/type-declarations.json
+++ b/test/corpus/diff-summaries/go/type-declarations.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -67,11 +67,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
3
]
}
@@ -82,11 +82,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -100,9 +100,20 @@
"filePaths": [
"type-declarations.go"
],
- "sha1": "262ad8491999ea66eb0f840c0b00851ebce2af55",
+ "patch": [
+ "diff --git a/type-declarations.go b/type-declarations.go",
+ "index e69de29..bad79f0 100644",
+ "--- a/type-declarations.go",
+ "+++ b/type-declarations.go",
+ "@@ -0,0 +1,5 @@",
+ "+type a b",
+ "+type (",
+ "+ a b",
+ "+ c d",
+ "+ )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "fca723574d0b8bd175dd8519e46147ee77738fcf"
+ "shas": "d09227c96ba4107fb4b848d1ef05e13e92fa41a7..172bba4f02bb5ce28cba422a72639f162f9f9d77"
}
,{
"testCaseDescription": "go-type-declarations-replacement-insert-test",
@@ -113,11 +124,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -128,11 +139,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
9
]
}
@@ -143,11 +154,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -158,9 +169,69 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
10
],
+ "end": [
+ 2,
+ 1
+ ]
+ }
+ },
+ "summary": "Added the ''\n' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 2
+ ],
+ "end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the '' ' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 6
+ ],
"end": [
4,
1
@@ -173,26 +244,26 @@
"span": {
"insert": {
"start": [
- 5,
+ 4,
2
],
"end": [
- 5,
+ 4,
3
]
}
},
- "summary": "Added the 'a' identifier"
+ "summary": "Added the 'c' identifier"
},
{
"span": {
"insert": {
"start": [
- 5,
+ 4,
3
],
"end": [
- 5,
+ 4,
5
]
}
@@ -203,26 +274,26 @@
"span": {
"insert": {
"start": [
- 5,
+ 4,
5
],
"end": [
- 5,
+ 4,
6
]
}
},
- "summary": "Added the 'b' identifier"
+ "summary": "Added the 'd' identifier"
},
{
"span": {
"insert": {
"start": [
- 5,
+ 4,
6
],
"end": [
- 6,
+ 5,
1
]
}
@@ -233,101 +304,56 @@
"span": {
"insert": {
"start": [
- 6,
- 2
- ],
- "end": [
- 6,
- 3
- ]
- }
- },
- "summary": "Added the 'c' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 6,
- 3
- ],
- "end": [
- 6,
- 5
- ]
- }
- },
- "summary": "Added the '' ' ERROR"
- },
- {
- "span": {
- "insert": {
- "start": [
- 6,
- 5
- ],
- "end": [
6,
6
+ ],
+ "end": [
+ 6,
+ 7
]
}
},
- "summary": "Added the 'd' identifier"
+ "summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
6,
- 6
+ 8
+ ],
+ "end": [
+ 6,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 1
],
"end": [
7,
- 1
+ 5
]
}
},
- "summary": "Added the ''\n' ERROR"
+ "summary": "Added the 'type' identifier"
},
{
"span": {
"insert": {
"start": [
8,
- 6
- ],
- "end": [
- 8,
- 7
- ]
- }
- },
- "summary": "Added the 'a' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 8
- ],
- "end": [
- 8,
- 9
- ]
- }
- },
- "summary": "Added the 'b' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 10,
2
],
"end": [
- 10,
+ 8,
3
]
}
@@ -338,11 +364,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
4
],
"end": [
- 10,
+ 8,
5
]
}
@@ -353,11 +379,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
2
],
"end": [
- 11,
+ 9,
3
]
}
@@ -368,196 +394,16 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
4
],
"end": [
- 11,
+ 9,
5
]
}
},
"summary": "Added the 'd' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 13,
- 6
- ],
- "end": [
- 13,
- 7
- ]
- }
- },
- "summary": "Added the 'a' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 13,
- 8
- ],
- "end": [
- 13,
- 9
- ]
- }
- },
- "summary": "Added the 'b' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 15,
- 2
- ],
- "end": [
- 15,
- 3
- ]
- }
- },
- "summary": "Added the 'a' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 15,
- 4
- ],
- "end": [
- 15,
- 5
- ]
- }
- },
- "summary": "Added the 'b' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 16,
- 2
- ],
- "end": [
- 16,
- 3
- ]
- }
- },
- "summary": "Added the 'c' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 16,
- 4
- ],
- "end": [
- 16,
- 5
- ]
- }
- },
- "summary": "Added the 'd' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 6
- ],
- "end": [
- 3,
- 7
- ]
- }
- },
- "summary": "Deleted the 'a' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 8
- ],
- "end": [
- 3,
- 9
- ]
- }
- },
- "summary": "Deleted the 'b' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 2
- ],
- "end": [
- 5,
- 3
- ]
- }
- },
- "summary": "Deleted the 'a' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 4
- ],
- "end": [
- 5,
- 5
- ]
- }
- },
- "summary": "Deleted the 'b' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 6,
- 2
- ],
- "end": [
- 6,
- 3
- ]
- }
- },
- "summary": "Deleted the 'c' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 6,
- 4
- ],
- "end": [
- 6,
- 5
- ]
- }
- },
- "summary": "Deleted the 'd' identifier"
}
]
},
@@ -566,9 +412,28 @@
"filePaths": [
"type-declarations.go"
],
- "sha1": "fca723574d0b8bd175dd8519e46147ee77738fcf",
+ "patch": [
+ "diff --git a/type-declarations.go b/type-declarations.go",
+ "index bad79f0..958d2f7 100644",
+ "--- a/type-declarations.go",
+ "+++ b/type-declarations.go",
+ "@@ -1,3 +1,13 @@",
+ "+type a' b'",
+ "+type (",
+ "+ a' b'",
+ "+ c' d'",
+ "+ )",
+ "+type a b",
+ "+type (",
+ "+ a b",
+ "+ c d",
+ "+ )",
+ " type a b",
+ " type (",
+ " a b"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f2cb3fb363af3bb68ded79ca28afdbbe401730fc"
+ "shas": "172bba4f02bb5ce28cba422a72639f162f9f9d77..b4f018a4bdea7885c96f8ee3ba341516c4c59f47"
}
,{
"testCaseDescription": "go-type-declarations-delete-insert-test",
@@ -579,11 +444,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -594,11 +459,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -609,11 +474,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -624,11 +489,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -639,11 +504,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
3
]
}
@@ -654,11 +519,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -669,11 +534,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
6
],
"end": [
- 8,
+ 6,
7
]
}
@@ -684,11 +549,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
8
],
"end": [
- 8,
+ 6,
9
]
}
@@ -699,11 +564,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
2
],
"end": [
- 10,
+ 8,
3
]
}
@@ -714,11 +579,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
4
],
"end": [
- 10,
+ 8,
5
]
}
@@ -729,11 +594,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
2
],
"end": [
- 11,
+ 9,
3
]
}
@@ -744,101 +609,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
4
],
"end": [
- 11,
- 5
- ]
- }
- },
- "summary": "Added the 'd' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 13,
- 6
- ],
- "end": [
- 13,
- 7
- ]
- }
- },
- "summary": "Added the 'a' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 13,
- 8
- ],
- "end": [
- 13,
- 9
- ]
- }
- },
- "summary": "Added the 'b' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 15,
- 2
- ],
- "end": [
- 15,
- 3
- ]
- }
- },
- "summary": "Added the 'a' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 15,
- 4
- ],
- "end": [
- 15,
- 5
- ]
- }
- },
- "summary": "Added the 'b' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 16,
- 2
- ],
- "end": [
- 16,
- 3
- ]
- }
- },
- "summary": "Added the 'c' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 16,
- 4
- ],
- "end": [
- 16,
+ 9,
5
]
}
@@ -849,11 +624,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -864,11 +639,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
9
]
}
@@ -879,11 +654,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -894,9 +669,69 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
10
],
+ "end": [
+ 2,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 2
+ ],
+ "end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the '' ' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 6
+ ],
"end": [
4,
1
@@ -909,26 +744,26 @@
"span": {
"delete": {
"start": [
- 5,
+ 4,
2
],
"end": [
- 5,
+ 4,
3
]
}
},
- "summary": "Deleted the 'a' identifier"
+ "summary": "Deleted the 'c' identifier"
},
{
"span": {
"delete": {
"start": [
- 5,
+ 4,
3
],
"end": [
- 5,
+ 4,
5
]
}
@@ -939,26 +774,26 @@
"span": {
"delete": {
"start": [
- 5,
+ 4,
5
],
"end": [
- 5,
+ 4,
6
]
}
},
- "summary": "Deleted the 'b' identifier"
+ "summary": "Deleted the 'd' identifier"
},
{
"span": {
"delete": {
"start": [
- 5,
+ 4,
6
],
"end": [
- 6,
+ 5,
1
]
}
@@ -969,101 +804,56 @@
"span": {
"delete": {
"start": [
- 6,
- 2
- ],
- "end": [
- 6,
- 3
- ]
- }
- },
- "summary": "Deleted the 'c' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 6,
- 3
- ],
- "end": [
- 6,
- 5
- ]
- }
- },
- "summary": "Deleted the '' ' ERROR"
- },
- {
- "span": {
- "delete": {
- "start": [
- 6,
- 5
- ],
- "end": [
6,
6
+ ],
+ "end": [
+ 6,
+ 7
]
}
},
- "summary": "Deleted the 'd' identifier"
+ "summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
6,
- 6
+ 8
+ ],
+ "end": [
+ 6,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 1
],
"end": [
7,
- 1
+ 5
]
}
},
- "summary": "Deleted the ''\n' ERROR"
+ "summary": "Deleted the 'type' identifier"
},
{
"span": {
"delete": {
"start": [
8,
- 6
- ],
- "end": [
- 8,
- 7
- ]
- }
- },
- "summary": "Deleted the 'a' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 8
- ],
- "end": [
- 8,
- 9
- ]
- }
- },
- "summary": "Deleted the 'b' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 10,
2
],
"end": [
- 10,
+ 8,
3
]
}
@@ -1074,11 +864,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
4
],
"end": [
- 10,
+ 8,
5
]
}
@@ -1089,11 +879,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
2
],
"end": [
- 11,
+ 9,
3
]
}
@@ -1104,101 +894,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
4
],
"end": [
- 11,
- 5
- ]
- }
- },
- "summary": "Deleted the 'd' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 13,
- 6
- ],
- "end": [
- 13,
- 7
- ]
- }
- },
- "summary": "Deleted the 'a' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 13,
- 8
- ],
- "end": [
- 13,
- 9
- ]
- }
- },
- "summary": "Deleted the 'b' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 15,
- 2
- ],
- "end": [
- 15,
- 3
- ]
- }
- },
- "summary": "Deleted the 'a' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 15,
- 4
- ],
- "end": [
- 15,
- 5
- ]
- }
- },
- "summary": "Deleted the 'b' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 16,
- 2
- ],
- "end": [
- 16,
- 3
- ]
- }
- },
- "summary": "Deleted the 'c' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 16,
- 4
- ],
- "end": [
- 16,
+ 9,
5
]
}
@@ -1212,9 +912,25 @@
"filePaths": [
"type-declarations.go"
],
- "sha1": "f2cb3fb363af3bb68ded79ca28afdbbe401730fc",
+ "patch": [
+ "diff --git a/type-declarations.go b/type-declarations.go",
+ "index 958d2f7..4243a63 100644",
+ "--- a/type-declarations.go",
+ "+++ b/type-declarations.go",
+ "@@ -1,7 +1,7 @@",
+ "-type a' b'",
+ "+type a b",
+ " type (",
+ "- a' b'",
+ "- c' d'",
+ "+ a b",
+ "+ c d",
+ " )",
+ " type a b",
+ " type ("
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c3e486b911d3d4a498a1a77a4701462146e81100"
+ "shas": "b4f018a4bdea7885c96f8ee3ba341516c4c59f47..677b3be6e4364df98c58067af7f5bcb1192d3875"
}
,{
"testCaseDescription": "go-type-declarations-replacement-test",
@@ -1225,11 +941,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -1240,11 +956,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
7
],
"end": [
- 3,
+ 1,
9
]
}
@@ -1255,11 +971,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
9
],
"end": [
- 3,
+ 1,
10
]
}
@@ -1270,9 +986,69 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
10
],
+ "end": [
+ 2,
+ 1
+ ]
+ }
+ },
+ "summary": "Added the ''\n' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 2
+ ],
+ "end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the '' ' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 6
+ ],
"end": [
4,
1
@@ -1285,26 +1061,26 @@
"span": {
"insert": {
"start": [
- 5,
+ 4,
2
],
"end": [
- 5,
+ 4,
3
]
}
},
- "summary": "Added the 'a' identifier"
+ "summary": "Added the 'c' identifier"
},
{
"span": {
"insert": {
"start": [
- 5,
+ 4,
3
],
"end": [
- 5,
+ 4,
5
]
}
@@ -1315,26 +1091,26 @@
"span": {
"insert": {
"start": [
- 5,
+ 4,
5
],
"end": [
- 5,
+ 4,
6
]
}
},
- "summary": "Added the 'b' identifier"
+ "summary": "Added the 'd' identifier"
},
{
"span": {
"insert": {
"start": [
- 5,
+ 4,
6
],
"end": [
- 6,
+ 5,
1
]
}
@@ -1346,10 +1122,85 @@
"insert": {
"start": [
6,
- 2
+ 6
],
"end": [
6,
+ 7
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 8
+ ],
+ "end": [
+ 6,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'type' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 2
+ ],
+ "end": [
+ 8,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 4
+ ],
+ "end": [
+ 8,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 2
+ ],
+ "end": [
+ 9,
3
]
}
@@ -1360,27 +1211,314 @@
"span": {
"insert": {
"start": [
- 6,
- 3
+ 9,
+ 4
],
"end": [
- 6,
+ 9,
5
]
}
},
- "summary": "Added the '' ' ERROR"
+ "summary": "Added the 'd' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 6
+ ],
+ "end": [
+ 1,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 8
+ ],
+ "end": [
+ 1,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 2
+ ],
+ "end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 4
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 2
+ ],
+ "end": [
+ 4,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 4
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'd' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 6
+ ],
+ "end": [
+ 6,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 8
+ ],
+ "end": [
+ 6,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 2
+ ],
+ "end": [
+ 8,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 4
+ ],
+ "end": [
+ 8,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 9,
+ 2
+ ],
+ "end": [
+ 9,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 9,
+ 4
+ ],
+ "end": [
+ 9,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'd' identifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "type-declarations.go"
+ ],
+ "patch": [
+ "diff --git a/type-declarations.go b/type-declarations.go",
+ "index 4243a63..958d2f7 100644",
+ "--- a/type-declarations.go",
+ "+++ b/type-declarations.go",
+ "@@ -1,7 +1,7 @@",
+ "-type a b",
+ "+type a' b'",
+ " type (",
+ "- a b",
+ "- c d",
+ "+ a' b'",
+ "+ c' d'",
+ " )",
+ " type a b",
+ " type ("
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "677b3be6e4364df98c58067af7f5bcb1192d3875..26240c7bacbed175805e95fc0b389cf748501a6b"
+}
+,{
+ "testCaseDescription": "go-type-declarations-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "type-declarations.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 6
+ ],
+ "end": [
+ 1,
+ 7
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
- 6,
- 5
+ 1,
+ 8
],
"end": [
- 6,
- 6
+ 1,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 2
+ ],
+ "end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 4
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 2
+ ],
+ "end": [
+ 4,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 4
+ ],
+ "end": [
+ 4,
+ 5
]
}
},
@@ -1391,7 +1529,37 @@
"insert": {
"start": [
6,
- 6
+ 7
+ ],
+ "end": [
+ 6,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the '' ' ERROR"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 9
+ ],
+ "end": [
+ 6,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 10
],
"end": [
7,
@@ -1406,40 +1574,10 @@
"insert": {
"start": [
8,
- 6
- ],
- "end": [
- 8,
- 7
- ]
- }
- },
- "summary": "Added the 'a' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 8
- ],
- "end": [
- 8,
- 9
- ]
- }
- },
- "summary": "Added the 'b' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 10,
2
],
"end": [
- 10,
+ 8,
3
]
}
@@ -1450,26 +1588,26 @@
"span": {
"insert": {
"start": [
- 10,
- 4
+ 8,
+ 6
],
"end": [
- 10,
- 5
+ 9,
+ 1
]
}
},
- "summary": "Added the 'b' identifier"
+ "summary": "Added the ''\n' ERROR"
},
{
"span": {
"insert": {
"start": [
- 11,
+ 9,
2
],
"end": [
- 11,
+ 9,
3
]
}
@@ -1480,102 +1618,27 @@
"span": {
"insert": {
"start": [
- 11,
- 4
+ 9,
+ 3
],
"end": [
- 11,
+ 9,
5
]
}
},
- "summary": "Added the 'd' identifier"
+ "summary": "Added the '' ' ERROR"
},
{
"span": {
"insert": {
"start": [
- 13,
+ 9,
+ 5
+ ],
+ "end": [
+ 9,
6
- ],
- "end": [
- 13,
- 7
- ]
- }
- },
- "summary": "Added the 'a' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 13,
- 8
- ],
- "end": [
- 13,
- 9
- ]
- }
- },
- "summary": "Added the 'b' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 15,
- 2
- ],
- "end": [
- 15,
- 3
- ]
- }
- },
- "summary": "Added the 'a' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 15,
- 4
- ],
- "end": [
- 15,
- 5
- ]
- }
- },
- "summary": "Added the 'b' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 16,
- 2
- ],
- "end": [
- 16,
- 3
- ]
- }
- },
- "summary": "Added the 'c' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 16,
- 4
- ],
- "end": [
- 16,
- 5
]
}
},
@@ -1586,40 +1649,10 @@
"delete": {
"start": [
3,
- 6
- ],
- "end": [
- 3,
- 7
- ]
- }
- },
- "summary": "Deleted the 'a' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 8
- ],
- "end": [
- 3,
- 9
- ]
- }
- },
- "summary": "Deleted the 'b' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -1630,41 +1663,206 @@
"span": {
"delete": {
"start": [
- 5,
- 4
+ 3,
+ 3
],
"end": [
- 5,
+ 3,
5
]
}
},
+ "summary": "Deleted the '' ' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 6
+ ]
+ }
+ },
"summary": "Deleted the 'b' identifier"
},
{
"span": {
"delete": {
"start": [
- 6,
+ 3,
+ 6
+ ],
+ "end": [
+ 4,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
2
],
"end": [
- 6,
+ 4,
3
]
}
},
"summary": "Deleted the 'c' identifier"
},
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the '' ' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 5
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'd' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 6
+ ],
+ "end": [
+ 5,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n' ERROR"
+ },
{
"span": {
"delete": {
"start": [
6,
- 4
+ 6
],
"end": [
6,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 8
+ ],
+ "end": [
+ 6,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'type' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 2
+ ],
+ "end": [
+ 8,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 4
+ ],
+ "end": [
+ 8,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 9,
+ 2
+ ],
+ "end": [
+ 9,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 9,
+ 4
+ ],
+ "end": [
+ 9,
5
]
}
@@ -1675,11 +1873,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 11,
6
],
"end": [
- 8,
+ 11,
7
]
}
@@ -1690,11 +1888,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 11,
8
],
"end": [
- 8,
+ 11,
9
]
}
@@ -1705,11 +1903,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 13,
2
],
"end": [
- 10,
+ 13,
3
]
}
@@ -1720,11 +1918,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 13,
4
],
"end": [
- 10,
+ 13,
5
]
}
@@ -1735,11 +1933,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 14,
2
],
"end": [
- 11,
+ 14,
3
]
}
@@ -1750,101 +1948,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 14,
4
],
"end": [
- 11,
- 5
- ]
- }
- },
- "summary": "Deleted the 'd' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 13,
- 6
- ],
- "end": [
- 13,
- 7
- ]
- }
- },
- "summary": "Deleted the 'a' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 13,
- 8
- ],
- "end": [
- 13,
- 9
- ]
- }
- },
- "summary": "Deleted the 'b' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 15,
- 2
- ],
- "end": [
- 15,
- 3
- ]
- }
- },
- "summary": "Deleted the 'a' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 15,
- 4
- ],
- "end": [
- 15,
- 5
- ]
- }
- },
- "summary": "Deleted the 'b' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 16,
- 2
- ],
- "end": [
- 16,
- 3
- ]
- }
- },
- "summary": "Deleted the 'c' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 16,
- 4
- ],
- "end": [
- 16,
+ 14,
5
]
}
@@ -1858,52 +1966,33 @@
"filePaths": [
"type-declarations.go"
],
- "sha1": "c3e486b911d3d4a498a1a77a4701462146e81100",
- "gitDir": "test/corpus/repos/go",
- "sha2": "ad50288fb7c188709119312ceac9bc0918e5d974"
-}
-,{
- "testCaseDescription": "go-type-declarations-delete-replacement-test",
- "expectedResult": {
- "changes": {
- "type-declarations.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 18,
- 1
- ]
- },
- {
- "start": [
- 1,
- 9
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
- },
- "summary": "Replaced the 'main' module with the 'main' identifier"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "type-declarations.go"
+ "patch": [
+ "diff --git a/type-declarations.go b/type-declarations.go",
+ "index 958d2f7..7447324 100644",
+ "--- a/type-declarations.go",
+ "+++ b/type-declarations.go",
+ "@@ -1,15 +1,10 @@",
+ "-type a' b'",
+ "-type (",
+ "- a' b'",
+ "- c' d'",
+ "- )",
+ " type a b",
+ " type (",
+ " a b",
+ " c d",
+ " )",
+ "-type a b",
+ "+type a' b'",
+ " type (",
+ "- a b",
+ "- c d",
+ "+ a' b'",
+ "+ c' d'",
+ " )"
],
- "sha1": "ad50288fb7c188709119312ceac9bc0918e5d974",
"gitDir": "test/corpus/repos/go",
- "sha2": "9792a447d6be637945761726ce60cae3a45486b2"
+ "shas": "26240c7bacbed175805e95fc0b389cf748501a6b..328de11cc8ee65cc28e8bc113c57592ae4cff91b"
}
,{
"testCaseDescription": "go-type-declarations-delete-test",
@@ -1914,11 +2003,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
7
]
}
@@ -1929,11 +2018,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -1944,11 +2033,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
2
],
"end": [
- 5,
+ 3,
3
]
}
@@ -1959,11 +2048,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -1974,11 +2063,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
3
]
}
@@ -1989,11 +2078,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
4
],
"end": [
- 6,
+ 4,
5
]
}
@@ -2007,9 +2096,23 @@
"filePaths": [
"type-declarations.go"
],
- "sha1": "9792a447d6be637945761726ce60cae3a45486b2",
+ "patch": [
+ "diff --git a/type-declarations.go b/type-declarations.go",
+ "index 7447324..9bffa13 100644",
+ "--- a/type-declarations.go",
+ "+++ b/type-declarations.go",
+ "@@ -1,8 +1,3 @@",
+ "-type a b",
+ "-type (",
+ "- a b",
+ "- c d",
+ "- )",
+ " type a' b'",
+ " type (",
+ " a' b'"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "db0806503d9690f63161fbc236c76ec9180e42e5"
+ "shas": "328de11cc8ee65cc28e8bc113c57592ae4cff91b..e6d67ba7232a82243566bd3f47aa147bc38b18eb"
}
,{
"testCaseDescription": "go-type-declarations-delete-rest-test",
@@ -2018,30 +2121,183 @@
"type-declarations.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 9
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 6
+ ],
+ "end": [
+ 1,
+ 7
+ ]
+ }
},
- "summary": "Replaced the 'main' identifier with the 'main' module"
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the '' ' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 9
+ ],
+ "end": [
+ 1,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 10
+ ],
+ "end": [
+ 2,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 2
+ ],
+ "end": [
+ 3,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the '' ' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 6
+ ],
+ "end": [
+ 4,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 2
+ ],
+ "end": [
+ 4,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the '' ' ERROR"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 5
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'd' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 6
+ ],
+ "end": [
+ 5,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the ''\n' ERROR"
}
]
},
@@ -2050,7 +2306,18 @@
"filePaths": [
"type-declarations.go"
],
- "sha1": "db0806503d9690f63161fbc236c76ec9180e42e5",
+ "patch": [
+ "diff --git a/type-declarations.go b/type-declarations.go",
+ "index 9bffa13..e69de29 100644",
+ "--- a/type-declarations.go",
+ "+++ b/type-declarations.go",
+ "@@ -1,5 +0,0 @@",
+ "-type a' b'",
+ "-type (",
+ "- a' b'",
+ "- c' d'",
+ "- )"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "475deec198e080301901a65778b6e2ee6255ee60"
+ "shas": "e6d67ba7232a82243566bd3f47aa147bc38b18eb..479bb7390b5a93cd2d670d77d3ac6bf6c4169be4"
}]
diff --git a/test/corpus/diff-summaries/go/type-switch-statements.json b/test/corpus/diff-summaries/go/type-switch-statements.json
index 8231cf036..2071c0128 100644
--- a/test/corpus/diff-summaries/go/type-switch-statements.json
+++ b/test/corpus/diff-summaries/go/type-switch-statements.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
16
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
8
]
}
@@ -52,11 +52,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
9
],
"end": [
- 6,
+ 4,
12
]
}
@@ -67,11 +67,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
10
]
}
@@ -85,9 +85,21 @@
"filePaths": [
"type-switch-statements.go"
],
- "sha1": "5ed5348fda2a0c23b658e6e2a4a918d6abfd9b09",
+ "patch": [
+ "diff --git a/type-switch-statements.go b/type-switch-statements.go",
+ "index e69de29..f353f0b 100644",
+ "--- a/type-switch-statements.go",
+ "+++ b/type-switch-statements.go",
+ "@@ -0,0 +1,6 @@",
+ "+switch e.(type) {",
+ "+ case []Person:",
+ "+ a()",
+ "+ case *Dog:",
+ "+ break",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "8c9e10a92d4b505bf5d75bb8d8d7f0d387cd3cd3"
+ "shas": "2de5024544064b228b54159d60307f986fdc8ee9..17bfceb9e9c2b372da22522f373195d94a74ad04"
}
,{
"testCaseDescription": "go-type-switch-statements-replacement-insert-test",
@@ -96,30 +108,153 @@
"type-switch-statements.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 9,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 8
+ ],
+ "end": [
+ 1,
+ 9
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 10
+ ],
+ "end": [
+ 2,
+ 16
+ ]
+ }
+ },
+ "summary": "Added the 'Person' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'a()' function call"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 9
+ ],
+ "end": [
+ 4,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'Dog' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 5,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'break' break_statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 8
+ ],
+ "end": [
+ 7,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the 'e' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 10
+ ],
+ "end": [
+ 8,
+ 16
+ ]
+ }
+ },
+ "summary": "Added the 'Person' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 5
+ ],
+ "end": [
+ 9,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'a()' function call"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 10,
+ 9
+ ],
+ "end": [
+ 10,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'Dog' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 11,
+ 5
+ ],
+ "end": [
+ 11,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'break' break_statement"
}
]
},
@@ -128,9 +263,30 @@
"filePaths": [
"type-switch-statements.go"
],
- "sha1": "8c9e10a92d4b505bf5d75bb8d8d7f0d387cd3cd3",
+ "patch": [
+ "diff --git a/type-switch-statements.go b/type-switch-statements.go",
+ "index f353f0b..0c6eb84 100644",
+ "--- a/type-switch-statements.go",
+ "+++ b/type-switch-statements.go",
+ "@@ -1,3 +1,15 @@",
+ "+switch b.(type) {",
+ "+ case []Person:",
+ "+ a()",
+ "+ case *Dog:",
+ "+ break",
+ "+}",
+ "+switch e.(type) {",
+ "+ case []Person:",
+ "+ a()",
+ "+ case *Dog:",
+ "+ break",
+ "+}",
+ " switch e.(type) {",
+ " case []Person:",
+ " a()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7b554c76f25a54ff17905bf91c4b438d610ce906"
+ "shas": "17bfceb9e9c2b372da22522f373195d94a74ad04..90cd615275a1f4328af6280571ff5bbb5a76dcae"
}
,{
"testCaseDescription": "go-type-switch-statements-delete-insert-test",
@@ -142,21 +298,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
},
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -171,9 +327,20 @@
"filePaths": [
"type-switch-statements.go"
],
- "sha1": "7b554c76f25a54ff17905bf91c4b438d610ce906",
+ "patch": [
+ "diff --git a/type-switch-statements.go b/type-switch-statements.go",
+ "index 0c6eb84..b373d6d 100644",
+ "--- a/type-switch-statements.go",
+ "+++ b/type-switch-statements.go",
+ "@@ -1,4 +1,4 @@",
+ "-switch b.(type) {",
+ "+switch e.(type) {",
+ " case []Person:",
+ " a()",
+ " case *Dog:"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "aa7c10f0b81dff8ff06579226a25180862120a0b"
+ "shas": "90cd615275a1f4328af6280571ff5bbb5a76dcae..dcee63cea9925a67454e2d836792c6523da654a0"
}
,{
"testCaseDescription": "go-type-switch-statements-replacement-test",
@@ -185,21 +352,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
},
{
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -214,9 +381,20 @@
"filePaths": [
"type-switch-statements.go"
],
- "sha1": "aa7c10f0b81dff8ff06579226a25180862120a0b",
+ "patch": [
+ "diff --git a/type-switch-statements.go b/type-switch-statements.go",
+ "index b373d6d..0c6eb84 100644",
+ "--- a/type-switch-statements.go",
+ "+++ b/type-switch-statements.go",
+ "@@ -1,4 +1,4 @@",
+ "-switch e.(type) {",
+ "+switch b.(type) {",
+ " case []Person:",
+ " a()",
+ " case *Dog:"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "4f512515a026daf778573a4ee70423cf19ffe392"
+ "shas": "dcee63cea9925a67454e2d836792c6523da654a0..c9b764e71359b28661197d853ccbfb0750405231"
}
,{
"testCaseDescription": "go-type-switch-statements-delete-replacement-test",
@@ -227,11 +405,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
@@ -242,11 +420,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
16
]
}
@@ -257,11 +435,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
8
]
}
@@ -272,11 +450,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
9
],
"end": [
- 6,
+ 4,
12
]
}
@@ -287,11 +465,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
10
]
}
@@ -302,11 +480,11 @@
"span": {
"delete": {
"start": [
- 9,
+ 7,
8
],
"end": [
- 9,
+ 7,
9
]
}
@@ -317,11 +495,11 @@
"span": {
"delete": {
"start": [
- 10,
+ 8,
10
],
"end": [
- 10,
+ 8,
16
]
}
@@ -332,11 +510,11 @@
"span": {
"delete": {
"start": [
- 11,
+ 9,
5
],
"end": [
- 11,
+ 9,
8
]
}
@@ -347,11 +525,11 @@
"span": {
"delete": {
"start": [
- 12,
+ 10,
9
],
"end": [
- 12,
+ 10,
12
]
}
@@ -362,11 +540,11 @@
"span": {
"delete": {
"start": [
- 13,
+ 11,
5
],
"end": [
- 13,
+ 11,
10
]
}
@@ -377,11 +555,11 @@
"span": {
"insert": {
"start": [
- 9,
+ 7,
8
],
"end": [
- 9,
+ 7,
9
]
}
@@ -392,11 +570,11 @@
"span": {
"insert": {
"start": [
- 10,
+ 8,
10
],
"end": [
- 10,
+ 8,
16
]
}
@@ -407,11 +585,11 @@
"span": {
"insert": {
"start": [
- 11,
+ 9,
5
],
"end": [
- 11,
+ 9,
8
]
}
@@ -422,11 +600,11 @@
"span": {
"insert": {
"start": [
- 12,
+ 10,
9
],
"end": [
- 12,
+ 10,
12
]
}
@@ -437,11 +615,11 @@
"span": {
"insert": {
"start": [
- 13,
+ 11,
5
],
"end": [
- 13,
+ 11,
10
]
}
@@ -455,55 +633,35 @@
"filePaths": [
"type-switch-statements.go"
],
- "sha1": "4f512515a026daf778573a4ee70423cf19ffe392",
+ "patch": [
+ "diff --git a/type-switch-statements.go b/type-switch-statements.go",
+ "index 0c6eb84..64567d6 100644",
+ "--- a/type-switch-statements.go",
+ "+++ b/type-switch-statements.go",
+ "@@ -1,16 +1,10 @@",
+ "-switch b.(type) {",
+ "- case []Person:",
+ "- a()",
+ "- case *Dog:",
+ "- break",
+ "-}",
+ " switch e.(type) {",
+ " case []Person:",
+ " a()",
+ " case *Dog:",
+ " break",
+ " }",
+ "-switch e.(type) {",
+ "+switch b.(type) {",
+ " case []Person:",
+ " a()",
+ " case *Dog:"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "94f94a0f60ffe393994e557cfc35fdda7e350d09"
+ "shas": "c9b764e71359b28661197d853ccbfb0750405231..1021943f2594b7cd8c977fd0e6cef06c34bd4d70"
}
,{
"testCaseDescription": "go-type-switch-statements-delete-test",
- "expectedResult": {
- "changes": {
- "type-switch-statements.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 9,
- 1
- ]
- }
- ]
- },
- "summary": "Replaced the 'main' module with the 'main' module"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "type-switch-statements.go"
- ],
- "sha1": "94f94a0f60ffe393994e557cfc35fdda7e350d09",
- "gitDir": "test/corpus/repos/go",
- "sha2": "aa78c757ce8c988cc95998bfc375aadda963b79d"
-}
-,{
- "testCaseDescription": "go-type-switch-statements-delete-rest-test",
"expectedResult": {
"changes": {
"type-switch-statements.go": [
@@ -511,26 +669,26 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
8
],
"end": [
- 3,
+ 1,
9
]
}
},
- "summary": "Deleted the 'b' identifier"
+ "summary": "Deleted the 'e' identifier"
},
{
"span": {
"delete": {
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
16
]
}
@@ -541,11 +699,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
5
],
"end": [
- 5,
+ 3,
8
]
}
@@ -556,11 +714,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
9
],
"end": [
- 6,
+ 4,
12
]
}
@@ -571,11 +729,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
5
],
"end": [
- 7,
+ 5,
10
]
}
@@ -589,7 +747,125 @@
"filePaths": [
"type-switch-statements.go"
],
- "sha1": "aa78c757ce8c988cc95998bfc375aadda963b79d",
+ "patch": [
+ "diff --git a/type-switch-statements.go b/type-switch-statements.go",
+ "index 64567d6..047534a 100644",
+ "--- a/type-switch-statements.go",
+ "+++ b/type-switch-statements.go",
+ "@@ -1,9 +1,3 @@",
+ "-switch e.(type) {",
+ "- case []Person:",
+ "- a()",
+ "- case *Dog:",
+ "- break",
+ "-}",
+ " switch b.(type) {",
+ " case []Person:",
+ " a()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "55c9268038cdb6e46dd211683ac12b462f9e590f"
+ "shas": "1021943f2594b7cd8c977fd0e6cef06c34bd4d70..501f3e52ab12fac877cd58fa6631284d8c7480ff"
+}
+,{
+ "testCaseDescription": "go-type-switch-statements-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "type-switch-statements.go": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 8
+ ],
+ "end": [
+ 1,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 10
+ ],
+ "end": [
+ 2,
+ 16
+ ]
+ }
+ },
+ "summary": "Deleted the 'Person' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 5
+ ],
+ "end": [
+ 3,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'a()' function call"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 9
+ ],
+ "end": [
+ 4,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the 'Dog' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 5
+ ],
+ "end": [
+ 5,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted the 'break' break_statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "type-switch-statements.go"
+ ],
+ "patch": [
+ "diff --git a/type-switch-statements.go b/type-switch-statements.go",
+ "index 047534a..e69de29 100644",
+ "--- a/type-switch-statements.go",
+ "+++ b/type-switch-statements.go",
+ "@@ -1,6 +0,0 @@",
+ "-switch b.(type) {",
+ "- case []Person:",
+ "- a()",
+ "- case *Dog:",
+ "- break",
+ "-}"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "501f3e52ab12fac877cd58fa6631284d8c7480ff..e544e711890744c45f9b49604be9c175422f7e15"
}]
diff --git a/test/corpus/diff-summaries/go/unary-expressions.json b/test/corpus/diff-summaries/go/unary-expressions.json
index 3df7df9db..7122797e9 100644
--- a/test/corpus/diff-summaries/go/unary-expressions.json
+++ b/test/corpus/diff-summaries/go/unary-expressions.json
@@ -1,48 +1,5 @@
[{
"testCaseDescription": "go-unary-expressions-insert-test",
- "expectedResult": {
- "changes": {
- "unary-expressions.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
- },
- "summary": "Replaced the 'main' module with the 'main' module"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "unary-expressions.go"
- ],
- "sha1": "423c95c361986c8807246777d0d1f5dd0602c5d7",
- "gitDir": "test/corpus/repos/go",
- "sha2": "12de993f257bdb9907574b17ef26c69eea4cecaa"
-}
-,{
- "testCaseDescription": "go-unary-expressions-replacement-insert-test",
"expectedResult": {
"changes": {
"unary-expressions.go": [
@@ -50,41 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
- 5
- ]
- }
- },
- "summary": "Added the 'b' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 7
- ]
- }
- },
- "summary": "Added the 'identifier()' function call"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 4
- ],
- "end": [
- 5,
+ 1,
5
]
}
@@ -95,11 +22,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 2,
1
],
"end": [
- 6,
+ 2,
7
]
}
@@ -113,9 +40,105 @@
"filePaths": [
"unary-expressions.go"
],
- "sha1": "12de993f257bdb9907574b17ef26c69eea4cecaa",
+ "patch": [
+ "diff --git a/unary-expressions.go b/unary-expressions.go",
+ "index e69de29..858c09a 100644",
+ "--- a/unary-expressions.go",
+ "+++ b/unary-expressions.go",
+ "@@ -0,0 +1,2 @@",
+ "+!<-a",
+ "+*foo()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "11145f78213cf405aad0a5d1324d6b806d3f472a"
+ "shas": "42975c2ba57995b8cc4cfe30c7599c673970dd25..383857c1c2527b50055c4dfe90fb44b26bf0fefa"
+}
+,{
+ "testCaseDescription": "go-unary-expressions-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "unary-expressions.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 4
+ ],
+ "end": [
+ 1,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 7
+ ]
+ }
+ },
+ "summary": "Added the 'identifier()' function call"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 4
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 7
+ ]
+ }
+ },
+ "summary": "Added the 'identifier()' function call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "unary-expressions.go"
+ ],
+ "patch": [
+ "diff --git a/unary-expressions.go b/unary-expressions.go",
+ "index 858c09a..0b42f98 100644",
+ "--- a/unary-expressions.go",
+ "+++ b/unary-expressions.go",
+ "@@ -1,2 +1,6 @@",
+ "+!<-b",
+ "+*bar()",
+ "+!<-a",
+ "+*foo()",
+ " !<-a",
+ " *foo()"
+ ],
+ "gitDir": "test/corpus/repos/go",
+ "shas": "383857c1c2527b50055c4dfe90fb44b26bf0fefa..9312cbe74e464febaa3f93fb1b2adf7011d1b95b"
}
,{
"testCaseDescription": "go-unary-expressions-delete-insert-test",
@@ -127,21 +150,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
},
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -154,21 +177,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
5
]
},
{
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
5
]
}
@@ -183,9 +206,22 @@
"filePaths": [
"unary-expressions.go"
],
- "sha1": "11145f78213cf405aad0a5d1324d6b806d3f472a",
+ "patch": [
+ "diff --git a/unary-expressions.go b/unary-expressions.go",
+ "index 0b42f98..25afb46 100644",
+ "--- a/unary-expressions.go",
+ "+++ b/unary-expressions.go",
+ "@@ -1,5 +1,5 @@",
+ "-!<-b",
+ "-*bar()",
+ "+!<-a",
+ "+*foo()",
+ " !<-a",
+ " *foo()",
+ " !<-a"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "fe320d2bd5724dc92c3702ebef1e3be53cf629d9"
+ "shas": "9312cbe74e464febaa3f93fb1b2adf7011d1b95b..57ec8fc14e1e8a6d8634011258174e08068a4198"
}
,{
"testCaseDescription": "go-unary-expressions-replacement-test",
@@ -197,21 +233,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
},
{
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -224,21 +260,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
5
]
},
{
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
5
]
}
@@ -253,9 +289,22 @@
"filePaths": [
"unary-expressions.go"
],
- "sha1": "fe320d2bd5724dc92c3702ebef1e3be53cf629d9",
+ "patch": [
+ "diff --git a/unary-expressions.go b/unary-expressions.go",
+ "index 25afb46..0b42f98 100644",
+ "--- a/unary-expressions.go",
+ "+++ b/unary-expressions.go",
+ "@@ -1,5 +1,5 @@",
+ "-!<-a",
+ "-*foo()",
+ "+!<-b",
+ "+*bar()",
+ " !<-a",
+ " *foo()",
+ " !<-a"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f4b3902991f22998eca4acc15dc987b62176c418"
+ "shas": "57ec8fc14e1e8a6d8634011258174e08068a4198..c8e2c9b5af896f4b2a72cc9862c60df9a1b65aa4"
}
,{
"testCaseDescription": "go-unary-expressions-delete-replacement-test",
@@ -266,11 +315,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -281,11 +330,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
7
]
}
@@ -296,11 +345,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -311,11 +360,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
7
]
}
@@ -326,11 +375,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
4
],
"end": [
- 5,
+ 3,
5
]
}
@@ -341,11 +390,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
7
]
}
@@ -359,9 +408,23 @@
"filePaths": [
"unary-expressions.go"
],
- "sha1": "f4b3902991f22998eca4acc15dc987b62176c418",
+ "patch": [
+ "diff --git a/unary-expressions.go b/unary-expressions.go",
+ "index 0b42f98..812fb68 100644",
+ "--- a/unary-expressions.go",
+ "+++ b/unary-expressions.go",
+ "@@ -1,6 +1,4 @@",
+ "-!<-b",
+ "-*bar()",
+ "-!<-a",
+ "-*foo()",
+ " !<-a",
+ " *foo()",
+ "+!<-b",
+ "+*bar()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3df238d0afc9c08d06ebe067685ec879aaab33a8"
+ "shas": "c8e2c9b5af896f4b2a72cc9862c60df9a1b65aa4..f3aa65ee6692f5aa37c6f8e6a01d2093e27999a0"
}
,{
"testCaseDescription": "go-unary-expressions-delete-test",
@@ -372,11 +435,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
4
],
"end": [
- 3,
+ 1,
5
]
}
@@ -387,11 +450,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
7
]
}
@@ -405,9 +468,19 @@
"filePaths": [
"unary-expressions.go"
],
- "sha1": "3df238d0afc9c08d06ebe067685ec879aaab33a8",
+ "patch": [
+ "diff --git a/unary-expressions.go b/unary-expressions.go",
+ "index 812fb68..6da661d 100644",
+ "--- a/unary-expressions.go",
+ "+++ b/unary-expressions.go",
+ "@@ -1,4 +1,2 @@",
+ "-!<-a",
+ "-*foo()",
+ " !<-b",
+ " *bar()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "8d525b8c16c2b71695c639ccd70ee8a054da5f9f"
+ "shas": "f3aa65ee6692f5aa37c6f8e6a01d2093e27999a0..da09442b50bcb67001af1f6599a2d2cd37c86907"
}
,{
"testCaseDescription": "go-unary-expressions-delete-rest-test",
@@ -416,30 +489,33 @@
"unary-expressions.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 13
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 4
+ ],
+ "end": [
+ 1,
+ 5
+ ]
+ }
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Deleted the 'b' identifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted the 'identifier()' function call"
}
]
},
@@ -448,7 +524,15 @@
"filePaths": [
"unary-expressions.go"
],
- "sha1": "8d525b8c16c2b71695c639ccd70ee8a054da5f9f",
+ "patch": [
+ "diff --git a/unary-expressions.go b/unary-expressions.go",
+ "index 6da661d..e69de29 100644",
+ "--- a/unary-expressions.go",
+ "+++ b/unary-expressions.go",
+ "@@ -1,2 +0,0 @@",
+ "-!<-b",
+ "-*bar()"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c084d45f7de68c3a9328f11b1ff483ad5260f06e"
+ "shas": "da09442b50bcb67001af1f6599a2d2cd37c86907..b3266e749035509bbbd882ef5e2d3ad93c3c60bf"
}]
diff --git a/test/corpus/diff-summaries/go/var-declarations-with-no-expressions.json b/test/corpus/diff-summaries/go/var-declarations-with-no-expressions.json
index ec28ba14e..5488ed154 100644
--- a/test/corpus/diff-summaries/go/var-declarations-with-no-expressions.json
+++ b/test/corpus/diff-summaries/go/var-declarations-with-no-expressions.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
20
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
20
]
}
@@ -55,9 +55,17 @@
"filePaths": [
"var-declarations-with-no-expressions.go"
],
- "sha1": "70ce013ae911ea6eada76f2e5739baddcd04613f",
+ "patch": [
+ "diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
+ "index e69de29..f156385 100644",
+ "--- a/var-declarations-with-no-expressions.go",
+ "+++ b/var-declarations-with-no-expressions.go",
+ "@@ -0,0 +1,2 @@",
+ "+var zero int",
+ "+var one, two uint64"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "cc1f8ac20228e18260eb8d54b2ba0ed54bb74630"
+ "shas": "a2b3bd32a19f7f76f1536197e193b8699b844991..a2b836d16d1c5f0e706cd50d82e0f04a5fb91a7a"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-replacement-insert-test",
@@ -68,11 +76,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
10
]
}
@@ -83,11 +91,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
16
]
}
@@ -98,11 +106,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
16
]
}
@@ -113,11 +121,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
13
]
}
@@ -128,11 +136,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
20
]
}
@@ -143,11 +151,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
20
]
}
@@ -161,9 +169,21 @@
"filePaths": [
"var-declarations-with-no-expressions.go"
],
- "sha1": "cc1f8ac20228e18260eb8d54b2ba0ed54bb74630",
+ "patch": [
+ "diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
+ "index f156385..f696db9 100644",
+ "--- a/var-declarations-with-no-expressions.go",
+ "+++ b/var-declarations-with-no-expressions.go",
+ "@@ -1,2 +1,6 @@",
+ "+var a int",
+ "+var b, c uint64",
+ "+var zero int",
+ "+var one, two uint64",
+ " var zero int",
+ " var one, two uint64"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "c0b885c04fe0c5033537181739830e44d9c3575d"
+ "shas": "a2b836d16d1c5f0e706cd50d82e0f04a5fb91a7a..de01c957dd54df2dd44c5e7c32b524ab0e5ae288"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-delete-insert-test",
@@ -175,21 +195,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
},
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
9
]
}
@@ -202,21 +222,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
},
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
}
@@ -229,21 +249,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
},
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
13
]
}
@@ -258,9 +278,22 @@
"filePaths": [
"var-declarations-with-no-expressions.go"
],
- "sha1": "c0b885c04fe0c5033537181739830e44d9c3575d",
+ "patch": [
+ "diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
+ "index f696db9..e5e3183 100644",
+ "--- a/var-declarations-with-no-expressions.go",
+ "+++ b/var-declarations-with-no-expressions.go",
+ "@@ -1,5 +1,5 @@",
+ "-var a int",
+ "-var b, c uint64",
+ "+var zero int",
+ "+var one, two uint64",
+ " var zero int",
+ " var one, two uint64",
+ " var zero int"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "ac406800d15885c84b561071d4dfc6df4a0d4d64"
+ "shas": "de01c957dd54df2dd44c5e7c32b524ab0e5ae288..ec8bb1e3302da7a2a19ced73e7de72165c0bc5cc"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-replacement-test",
@@ -272,21 +305,21 @@
"replace": [
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
9
]
},
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
}
@@ -299,21 +332,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
6
]
}
@@ -326,21 +359,21 @@
"replace": [
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
13
]
},
{
"start": [
- 4,
+ 2,
8
],
"end": [
- 4,
+ 2,
9
]
}
@@ -355,9 +388,22 @@
"filePaths": [
"var-declarations-with-no-expressions.go"
],
- "sha1": "ac406800d15885c84b561071d4dfc6df4a0d4d64",
+ "patch": [
+ "diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
+ "index e5e3183..f696db9 100644",
+ "--- a/var-declarations-with-no-expressions.go",
+ "+++ b/var-declarations-with-no-expressions.go",
+ "@@ -1,5 +1,5 @@",
+ "-var zero int",
+ "-var one, two uint64",
+ "+var a int",
+ "+var b, c uint64",
+ " var zero int",
+ " var one, two uint64",
+ " var zero int"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "21e30df645b4718de28a23a53812adeff14ec120"
+ "shas": "ec8bb1e3302da7a2a19ced73e7de72165c0bc5cc..abc39ff623686b60f6dfb97f81a22bc99616fc32"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-delete-replacement-test",
@@ -368,11 +414,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
10
]
}
@@ -383,11 +429,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
16
]
}
@@ -398,11 +444,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
16
]
}
@@ -413,11 +459,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
13
]
}
@@ -428,11 +474,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
20
]
}
@@ -443,11 +489,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
20
]
}
@@ -458,11 +504,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
10
]
}
@@ -473,11 +519,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
16
]
}
@@ -488,11 +534,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
16
]
}
@@ -506,9 +552,23 @@
"filePaths": [
"var-declarations-with-no-expressions.go"
],
- "sha1": "21e30df645b4718de28a23a53812adeff14ec120",
+ "patch": [
+ "diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
+ "index f696db9..137ee10 100644",
+ "--- a/var-declarations-with-no-expressions.go",
+ "+++ b/var-declarations-with-no-expressions.go",
+ "@@ -1,6 +1,4 @@",
+ "-var a int",
+ "-var b, c uint64",
+ "-var zero int",
+ "-var one, two uint64",
+ " var zero int",
+ " var one, two uint64",
+ "+var a int",
+ "+var b, c uint64"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7f979d33c8675dcf2060cca3ee72e2f3df901e76"
+ "shas": "abc39ff623686b60f6dfb97f81a22bc99616fc32..ca2096e1754ebad8a421c0aec68b934eb6fe5946"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-delete-test",
@@ -519,11 +579,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -534,11 +594,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
20
]
}
@@ -549,11 +609,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
20
]
}
@@ -567,9 +627,19 @@
"filePaths": [
"var-declarations-with-no-expressions.go"
],
- "sha1": "7f979d33c8675dcf2060cca3ee72e2f3df901e76",
+ "patch": [
+ "diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
+ "index 137ee10..443ec9e 100644",
+ "--- a/var-declarations-with-no-expressions.go",
+ "+++ b/var-declarations-with-no-expressions.go",
+ "@@ -1,4 +1,2 @@",
+ "-var zero int",
+ "-var one, two uint64",
+ " var a int",
+ " var b, c uint64"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "5e63095f508ef9950f3ea36b9db98288c0a0b736"
+ "shas": "ca2096e1754ebad8a421c0aec68b934eb6fe5946..7cde9f681f73bc4b0fe063954142d9aac568b776"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-delete-rest-test",
@@ -580,11 +650,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
10
]
}
@@ -595,11 +665,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
16
]
}
@@ -610,11 +680,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
16
]
}
@@ -628,7 +698,15 @@
"filePaths": [
"var-declarations-with-no-expressions.go"
],
- "sha1": "5e63095f508ef9950f3ea36b9db98288c0a0b736",
+ "patch": [
+ "diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
+ "index 443ec9e..e69de29 100644",
+ "--- a/var-declarations-with-no-expressions.go",
+ "+++ b/var-declarations-with-no-expressions.go",
+ "@@ -1,2 +0,0 @@",
+ "-var a int",
+ "-var b, c uint64"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "3f6fa7c6f499951a277e9ae6edce3681134ef5d9"
+ "shas": "7cde9f681f73bc4b0fe063954142d9aac568b776..7ec7378727f160ff6fb78761d149f5f110898c3e"
}]
diff --git a/test/corpus/diff-summaries/go/var-declarations-with-types.json b/test/corpus/diff-summaries/go/var-declarations-with-types.json
index 27894b350..b005d2690 100644
--- a/test/corpus/diff-summaries/go/var-declarations-with-types.json
+++ b/test/corpus/diff-summaries/go/var-declarations-with-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
17
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
27
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
27
]
}
@@ -55,9 +55,17 @@
"filePaths": [
"var-declarations-with-types.go"
],
- "sha1": "560d069610442142d3191d7af8ea8e1a2ebfb6ca",
+ "patch": [
+ "diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
+ "index e69de29..7fa0f78 100644",
+ "--- a/var-declarations-with-types.go",
+ "+++ b/var-declarations-with-types.go",
+ "@@ -0,0 +1,2 @@",
+ "+var zero int = 0",
+ "+var one, two uint64 = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "d2c92ac70f8e73adf099bc0e290820d6eb845995"
+ "shas": "e8cad3a47721767f585896752477a07578a6ae45..5b28fe9002c6b7f4d200b92c3c4bed53f4c52999"
}
,{
"testCaseDescription": "go-var-declarations-with-types-replacement-insert-test",
@@ -68,11 +76,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
14
]
}
@@ -83,11 +91,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
24
]
}
@@ -98,11 +106,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
24
]
}
@@ -113,11 +121,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
17
]
}
@@ -128,11 +136,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
27
]
}
@@ -143,11 +151,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
27
]
}
@@ -161,9 +169,21 @@
"filePaths": [
"var-declarations-with-types.go"
],
- "sha1": "d2c92ac70f8e73adf099bc0e290820d6eb845995",
+ "patch": [
+ "diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
+ "index 7fa0f78..bf0a293 100644",
+ "--- a/var-declarations-with-types.go",
+ "+++ b/var-declarations-with-types.go",
+ "@@ -1,2 +1,6 @@",
+ "+var a int = 0",
+ "+ var b, c uint64 = 1, 2",
+ "+var zero int = 0",
+ "+var one, two uint64 = 1, 2",
+ " var zero int = 0",
+ " var one, two uint64 = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "152f26eaa12a8990773283c45ad83d581f49f6ac"
+ "shas": "5b28fe9002c6b7f4d200b92c3c4bed53f4c52999..9a2b636002071173ed229f3479690cdcb6340b2b"
}
,{
"testCaseDescription": "go-var-declarations-with-types-delete-insert-test",
@@ -175,81 +195,81 @@
"replace": [
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
},
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
9
]
}
]
},
- "summary": "Replaced the 'a' identifier with the 'zero' identifier in the zero variable of the 'main' module"
+ "summary": "Replaced the 'a' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
},
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
}
]
},
- "summary": "Replaced the 'b' identifier with the 'one' identifier in the one variable of the 'main' module"
+ "summary": "Replaced the 'b' identifier with the 'one' identifier in the one variable"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
},
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
13
]
}
]
},
- "summary": "Replaced the 'c' identifier with the 'two' identifier in the two variable of the 'main' module"
+ "summary": "Replaced the 'c' identifier with the 'two' identifier in the two variable"
}
]
},
@@ -258,9 +278,22 @@
"filePaths": [
"var-declarations-with-types.go"
],
- "sha1": "152f26eaa12a8990773283c45ad83d581f49f6ac",
+ "patch": [
+ "diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
+ "index bf0a293..cba22b9 100644",
+ "--- a/var-declarations-with-types.go",
+ "+++ b/var-declarations-with-types.go",
+ "@@ -1,5 +1,5 @@",
+ "-var a int = 0",
+ "- var b, c uint64 = 1, 2",
+ "+var zero int = 0",
+ "+var one, two uint64 = 1, 2",
+ " var zero int = 0",
+ " var one, two uint64 = 1, 2",
+ " var zero int = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "9c15c981626ece122958d534391d1cd11500823f"
+ "shas": "9a2b636002071173ed229f3479690cdcb6340b2b..2e8341b5c732a5cee90db221775545f69821fa61"
}
,{
"testCaseDescription": "go-var-declarations-with-types-replacement-test",
@@ -272,81 +305,81 @@
"replace": [
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
9
]
},
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
6
]
}
]
},
- "summary": "Replaced the 'zero' identifier with the 'a' identifier in the a variable of the 'main' module"
+ "summary": "Replaced the 'zero' identifier with the 'a' identifier in the a variable"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
5
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
7
]
}
]
},
- "summary": "Replaced the 'one' identifier with the 'b' identifier in the b variable of the 'main' module"
+ "summary": "Replaced the 'one' identifier with the 'b' identifier in the b variable"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
10
],
"end": [
- 4,
+ 2,
13
]
},
{
"start": [
- 4,
+ 2,
9
],
"end": [
- 4,
+ 2,
10
]
}
]
},
- "summary": "Replaced the 'two' identifier with the 'c' identifier in the c variable of the 'main' module"
+ "summary": "Replaced the 'two' identifier with the 'c' identifier in the c variable"
}
]
},
@@ -355,9 +388,22 @@
"filePaths": [
"var-declarations-with-types.go"
],
- "sha1": "9c15c981626ece122958d534391d1cd11500823f",
+ "patch": [
+ "diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
+ "index cba22b9..bf0a293 100644",
+ "--- a/var-declarations-with-types.go",
+ "+++ b/var-declarations-with-types.go",
+ "@@ -1,5 +1,5 @@",
+ "-var zero int = 0",
+ "-var one, two uint64 = 1, 2",
+ "+var a int = 0",
+ "+ var b, c uint64 = 1, 2",
+ " var zero int = 0",
+ " var one, two uint64 = 1, 2",
+ " var zero int = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "cefe840a6a8540095390d13aa58ea3124dbda0fc"
+ "shas": "2e8341b5c732a5cee90db221775545f69821fa61..324bbd99a82f7bd7b4d6015f3b6d344f39fb1b25"
}
,{
"testCaseDescription": "go-var-declarations-with-types-delete-replacement-test",
@@ -368,11 +414,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
14
]
}
@@ -383,11 +429,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
24
]
}
@@ -398,11 +444,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
24
]
}
@@ -413,11 +459,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
17
]
}
@@ -428,11 +474,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
27
]
}
@@ -443,11 +489,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
27
]
}
@@ -458,11 +504,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
14
]
}
@@ -473,11 +519,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
24
]
}
@@ -488,11 +534,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
2
],
"end": [
- 6,
+ 4,
24
]
}
@@ -506,9 +552,23 @@
"filePaths": [
"var-declarations-with-types.go"
],
- "sha1": "cefe840a6a8540095390d13aa58ea3124dbda0fc",
+ "patch": [
+ "diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
+ "index bf0a293..bd11fef 100644",
+ "--- a/var-declarations-with-types.go",
+ "+++ b/var-declarations-with-types.go",
+ "@@ -1,6 +1,4 @@",
+ "-var a int = 0",
+ "- var b, c uint64 = 1, 2",
+ "-var zero int = 0",
+ "-var one, two uint64 = 1, 2",
+ " var zero int = 0",
+ " var one, two uint64 = 1, 2",
+ "+var a int = 0",
+ "+ var b, c uint64 = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7611c6e70f70c76bb7d56d3996937b80c11e0ab4"
+ "shas": "324bbd99a82f7bd7b4d6015f3b6d344f39fb1b25..6864d4222bcdf5c352c42623d77a94fc8aa74a5b"
}
,{
"testCaseDescription": "go-var-declarations-with-types-delete-test",
@@ -519,11 +579,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
17
]
}
@@ -534,11 +594,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
27
]
}
@@ -549,11 +609,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
27
]
}
@@ -567,9 +627,19 @@
"filePaths": [
"var-declarations-with-types.go"
],
- "sha1": "7611c6e70f70c76bb7d56d3996937b80c11e0ab4",
+ "patch": [
+ "diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
+ "index bd11fef..6e0b7e7 100644",
+ "--- a/var-declarations-with-types.go",
+ "+++ b/var-declarations-with-types.go",
+ "@@ -1,4 +1,2 @@",
+ "-var zero int = 0",
+ "-var one, two uint64 = 1, 2",
+ " var a int = 0",
+ " var b, c uint64 = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "94b59191a5053d07a4fd33841213f6ee78ee13bf"
+ "shas": "6864d4222bcdf5c352c42623d77a94fc8aa74a5b..61b82a1db7b24aa0535c03fd7f41164e89045d27"
}
,{
"testCaseDescription": "go-var-declarations-with-types-delete-rest-test",
@@ -580,11 +650,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
14
]
}
@@ -595,11 +665,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
24
]
}
@@ -610,11 +680,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
2
],
"end": [
- 4,
+ 2,
24
]
}
@@ -628,7 +698,15 @@
"filePaths": [
"var-declarations-with-types.go"
],
- "sha1": "94b59191a5053d07a4fd33841213f6ee78ee13bf",
+ "patch": [
+ "diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
+ "index 6e0b7e7..e69de29 100644",
+ "--- a/var-declarations-with-types.go",
+ "+++ b/var-declarations-with-types.go",
+ "@@ -1,2 +0,0 @@",
+ "-var a int = 0",
+ "- var b, c uint64 = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "70ce013ae911ea6eada76f2e5739baddcd04613f"
+ "shas": "61b82a1db7b24aa0535c03fd7f41164e89045d27..a2b3bd32a19f7f76f1536197e193b8699b844991"
}]
diff --git a/test/corpus/diff-summaries/go/var-declarations-without-types.json b/test/corpus/diff-summaries/go/var-declarations-without-types.json
index 38b0e2ae3..8d1f0d0a5 100644
--- a/test/corpus/diff-summaries/go/var-declarations-without-types.json
+++ b/test/corpus/diff-summaries/go/var-declarations-without-types.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -25,9 +25,16 @@
"filePaths": [
"var-declarations-without-types.go"
],
- "sha1": "45b551f3f778995db1cbc9c4f64fc2a76995f41e",
+ "patch": [
+ "diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
+ "index e69de29..8c7993a 100644",
+ "--- a/var-declarations-without-types.go",
+ "+++ b/var-declarations-without-types.go",
+ "@@ -0,0 +1 @@",
+ "+var zero = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "6aa89fd9d53f9b40aebc5975b8a727d9a21b180b"
+ "shas": "95f53bbe92bd5841e140af869c4f35cb74379028..52b1ec2c1e475877223a656dd96d72fdb804f91a"
}
,{
"testCaseDescription": "go-var-declarations-without-types-replacement-insert-test",
@@ -38,11 +45,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
20
]
}
@@ -53,11 +60,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
20
]
}
@@ -68,11 +75,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
13
]
}
@@ -86,9 +93,18 @@
"filePaths": [
"var-declarations-without-types.go"
],
- "sha1": "6aa89fd9d53f9b40aebc5975b8a727d9a21b180b",
+ "patch": [
+ "diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
+ "index 8c7993a..80fe8ba 100644",
+ "--- a/var-declarations-without-types.go",
+ "+++ b/var-declarations-without-types.go",
+ "@@ -1 +1,3 @@",
+ "+var one, two = 1, 2",
+ "+var zero = 0",
+ " var zero = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "7c9ca82a0940fbb2d8545cf5bb423211cdc6bc5e"
+ "shas": "52b1ec2c1e475877223a656dd96d72fdb804f91a..fe75b1bdfc43772e3d24948192fc07e698745980"
}
,{
"testCaseDescription": "go-var-declarations-without-types-delete-insert-test",
@@ -100,64 +116,64 @@
"replace": [
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
9
]
}
]
},
- "summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero variable of the 'main' module"
+ "summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
16
],
"end": [
- 3,
+ 1,
17
]
},
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
13
]
}
]
},
- "summary": "Replaced '1' with '0' in the zero variable of the 'main' module"
+ "summary": "Replaced '1' with '0' in the zero variable"
},
{
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
20
]
}
@@ -171,9 +187,19 @@
"filePaths": [
"var-declarations-without-types.go"
],
- "sha1": "7c9ca82a0940fbb2d8545cf5bb423211cdc6bc5e",
+ "patch": [
+ "diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
+ "index 80fe8ba..c4df5f9 100644",
+ "--- a/var-declarations-without-types.go",
+ "+++ b/var-declarations-without-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-var one, two = 1, 2",
+ "+var zero = 0",
+ " var zero = 0",
+ " var zero = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e26bf19b3efa7ad66570dd9ba9a4b5dea2a06487"
+ "shas": "fe75b1bdfc43772e3d24948192fc07e698745980..35cb02da912d11d0f08767f9473f097b940abd00"
}
,{
"testCaseDescription": "go-var-declarations-without-types-replacement-test",
@@ -185,64 +211,64 @@
"replace": [
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
9
]
},
{
"start": [
- 3,
+ 1,
5
],
"end": [
- 3,
+ 1,
8
]
}
]
},
- "summary": "Replaced the 'zero' identifier with the 'one' identifier in the one variable of the 'main' module"
+ "summary": "Replaced the 'zero' identifier with the 'one' identifier in the one variable"
},
{
"span": {
"replace": [
{
"start": [
- 3,
+ 1,
12
],
"end": [
- 3,
+ 1,
13
]
},
{
"start": [
- 3,
+ 1,
16
],
"end": [
- 3,
+ 1,
17
]
}
]
},
- "summary": "Replaced '0' with '1' in the one variable of the 'main' module"
+ "summary": "Replaced '0' with '1' in the one variable"
},
{
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
20
]
}
@@ -256,9 +282,19 @@
"filePaths": [
"var-declarations-without-types.go"
],
- "sha1": "e26bf19b3efa7ad66570dd9ba9a4b5dea2a06487",
+ "patch": [
+ "diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
+ "index c4df5f9..80fe8ba 100644",
+ "--- a/var-declarations-without-types.go",
+ "+++ b/var-declarations-without-types.go",
+ "@@ -1,3 +1,3 @@",
+ "-var zero = 0",
+ "+var one, two = 1, 2",
+ " var zero = 0",
+ " var zero = 0"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "38532e82f3d975ef8fd20cb67547ad4141a4aa36"
+ "shas": "35cb02da912d11d0f08767f9473f097b940abd00..eb7d7dcbf668189e8a180beda45aa6bbcbeb817d"
}
,{
"testCaseDescription": "go-var-declarations-without-types-delete-replacement-test",
@@ -269,11 +305,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
20
]
}
@@ -284,11 +320,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
20
]
}
@@ -299,11 +335,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
13
]
}
@@ -314,11 +350,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
20
]
}
@@ -329,11 +365,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
20
]
}
@@ -347,9 +383,19 @@
"filePaths": [
"var-declarations-without-types.go"
],
- "sha1": "38532e82f3d975ef8fd20cb67547ad4141a4aa36",
+ "patch": [
+ "diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
+ "index 80fe8ba..0d0b543 100644",
+ "--- a/var-declarations-without-types.go",
+ "+++ b/var-declarations-without-types.go",
+ "@@ -1,3 +1,2 @@",
+ "-var one, two = 1, 2",
+ "-var zero = 0",
+ " var zero = 0",
+ "+var one, two = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "5cc9846fff4ba05c5be09b9a8c110b587bd8b62c"
+ "shas": "eb7d7dcbf668189e8a180beda45aa6bbcbeb817d..ab6d3f53b7dda2803a06b9ea08447a5ff7a3ae54"
}
,{
"testCaseDescription": "go-var-declarations-without-types-delete-test",
@@ -360,11 +406,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
13
]
}
@@ -378,9 +424,17 @@
"filePaths": [
"var-declarations-without-types.go"
],
- "sha1": "5cc9846fff4ba05c5be09b9a8c110b587bd8b62c",
+ "patch": [
+ "diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
+ "index 0d0b543..c4a6ab5 100644",
+ "--- a/var-declarations-without-types.go",
+ "+++ b/var-declarations-without-types.go",
+ "@@ -1,2 +1 @@",
+ "-var zero = 0",
+ " var one, two = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "2a85e7f986b54fc05cac2eb26b0f40847c04b903"
+ "shas": "ab6d3f53b7dda2803a06b9ea08447a5ff7a3ae54..ba8ea109550f5ea74bcca7e3856ddb339611f0de"
}
,{
"testCaseDescription": "go-var-declarations-without-types-delete-rest-test",
@@ -391,11 +445,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
20
]
}
@@ -406,11 +460,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
20
]
}
@@ -424,7 +478,14 @@
"filePaths": [
"var-declarations-without-types.go"
],
- "sha1": "2a85e7f986b54fc05cac2eb26b0f40847c04b903",
+ "patch": [
+ "diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
+ "index c4a6ab5..e69de29 100644",
+ "--- a/var-declarations-without-types.go",
+ "+++ b/var-declarations-without-types.go",
+ "@@ -1 +0,0 @@",
+ "-var one, two = 1, 2"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "560d069610442142d3191d7af8ea8e1a2ebfb6ca"
+ "shas": "ba8ea109550f5ea74bcca7e3856ddb339611f0de..e8cad3a47721767f585896752477a07578a6ae45"
}]
diff --git a/test/corpus/diff-summaries/go/variadic-function-declarations.json b/test/corpus/diff-summaries/go/variadic-function-declarations.json
index 44724badf..3b3978695 100644
--- a/test/corpus/diff-summaries/go/variadic-function-declarations.json
+++ b/test/corpus/diff-summaries/go/variadic-function-declarations.json
@@ -7,11 +7,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -22,11 +22,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
19
]
}
@@ -37,11 +37,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
23
]
}
@@ -55,9 +55,18 @@
"filePaths": [
"variadic-function-declarations.go"
],
- "sha1": "1011eae016159133bb9b3305fa29900aa6f06827",
+ "patch": [
+ "diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
+ "index e69de29..e9d461f 100644",
+ "--- a/variadic-function-declarations.go",
+ "+++ b/variadic-function-declarations.go",
+ "@@ -0,0 +1,3 @@",
+ "+func f1(a ...*int) {}",
+ "+func f2(...int) {}",
+ "+func f3(a, ...bool) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "55231bf51a6d46385791a80a387bba6b481cce3a"
+ "shas": "256c131008b104fa15d57c0f3ff56131c11337fe..b6ef32833f1cf331e26caedfd359c593f9b370b9"
}
,{
"testCaseDescription": "go-variadic-function-declarations-replacement-insert-test",
@@ -68,11 +77,11 @@
"span": {
"insert": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -83,11 +92,11 @@
"span": {
"insert": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
19
]
}
@@ -98,11 +107,11 @@
"span": {
"insert": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
23
]
}
@@ -113,11 +122,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
22
]
}
@@ -128,11 +137,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
19
]
}
@@ -143,11 +152,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
23
]
}
@@ -161,9 +170,24 @@
"filePaths": [
"variadic-function-declarations.go"
],
- "sha1": "55231bf51a6d46385791a80a387bba6b481cce3a",
+ "patch": [
+ "diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
+ "index e9d461f..1e4f816 100644",
+ "--- a/variadic-function-declarations.go",
+ "+++ b/variadic-function-declarations.go",
+ "@@ -1,3 +1,9 @@",
+ "+func g1(a ...*int) {}",
+ "+func g2(...int) {}",
+ "+func g3(a, ...bool) {}",
+ "+func f1(a ...*int) {}",
+ "+func f2(...int) {}",
+ "+func f3(a, ...bool) {}",
+ " func f1(a ...*int) {}",
+ " func f2(...int) {}",
+ " func f3(a, ...bool) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f61b087e33996e9582f497ed495b150158b0030f"
+ "shas": "b6ef32833f1cf331e26caedfd359c593f9b370b9..ef0f85884738262f219743f46d645a73d12f5b99"
}
,{
"testCaseDescription": "go-variadic-function-declarations-delete-insert-test",
@@ -175,81 +199,81 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
]
},
- "summary": "Replaced the 'g1' identifier with the 'f1' identifier in the f1 function of the 'main' module"
+ "summary": "Replaced the 'g1' identifier with the 'f1' identifier in the f1 function"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
]
},
- "summary": "Replaced the 'g2' identifier with the 'f2' identifier in the f2 function of the 'main' module"
+ "summary": "Replaced the 'g2' identifier with the 'f2' identifier in the f2 function"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
]
},
- "summary": "Replaced the 'g3' identifier with the 'f3' identifier in the f3 function of the 'main' module"
+ "summary": "Replaced the 'g3' identifier with the 'f3' identifier in the f3 function"
}
]
},
@@ -258,9 +282,24 @@
"filePaths": [
"variadic-function-declarations.go"
],
- "sha1": "f61b087e33996e9582f497ed495b150158b0030f",
+ "patch": [
+ "diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
+ "index 1e4f816..3198ec6 100644",
+ "--- a/variadic-function-declarations.go",
+ "+++ b/variadic-function-declarations.go",
+ "@@ -1,6 +1,6 @@",
+ "-func g1(a ...*int) {}",
+ "-func g2(...int) {}",
+ "-func g3(a, ...bool) {}",
+ "+func f1(a ...*int) {}",
+ "+func f2(...int) {}",
+ "+func f3(a, ...bool) {}",
+ " func f1(a ...*int) {}",
+ " func f2(...int) {}",
+ " func f3(a, ...bool) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "b6501ace5d04c639c61e4600f543ec61a1557b1b"
+ "shas": "ef0f85884738262f219743f46d645a73d12f5b99..6920ba9ae6296e24e09e55ea342020521f5443b7"
}
,{
"testCaseDescription": "go-variadic-function-declarations-replacement-test",
@@ -272,81 +311,81 @@
"replace": [
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
},
{
"start": [
- 3,
+ 1,
6
],
"end": [
- 3,
+ 1,
8
]
}
]
},
- "summary": "Replaced the 'f1' identifier with the 'g1' identifier in the g1 function of the 'main' module"
+ "summary": "Replaced the 'f1' identifier with the 'g1' identifier in the g1 function"
},
{
"span": {
"replace": [
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
},
{
"start": [
- 4,
+ 2,
6
],
"end": [
- 4,
+ 2,
8
]
}
]
},
- "summary": "Replaced the 'f2' identifier with the 'g2' identifier in the g2 function of the 'main' module"
+ "summary": "Replaced the 'f2' identifier with the 'g2' identifier in the g2 function"
},
{
"span": {
"replace": [
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
},
{
"start": [
- 5,
+ 3,
6
],
"end": [
- 5,
+ 3,
8
]
}
]
},
- "summary": "Replaced the 'f3' identifier with the 'g3' identifier in the g3 function of the 'main' module"
+ "summary": "Replaced the 'f3' identifier with the 'g3' identifier in the g3 function"
}
]
},
@@ -355,9 +394,24 @@
"filePaths": [
"variadic-function-declarations.go"
],
- "sha1": "b6501ace5d04c639c61e4600f543ec61a1557b1b",
+ "patch": [
+ "diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
+ "index 3198ec6..1e4f816 100644",
+ "--- a/variadic-function-declarations.go",
+ "+++ b/variadic-function-declarations.go",
+ "@@ -1,6 +1,6 @@",
+ "-func f1(a ...*int) {}",
+ "-func f2(...int) {}",
+ "-func f3(a, ...bool) {}",
+ "+func g1(a ...*int) {}",
+ "+func g2(...int) {}",
+ "+func g3(a, ...bool) {}",
+ " func f1(a ...*int) {}",
+ " func f2(...int) {}",
+ " func f3(a, ...bool) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "5c6438d74774c5505b9710c5095be94697ab5fdc"
+ "shas": "6920ba9ae6296e24e09e55ea342020521f5443b7..ffa8638d6bc29fe639cc3a3bdcb94d61b5c35336"
}
,{
"testCaseDescription": "go-variadic-function-declarations-delete-replacement-test",
@@ -368,11 +422,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -383,11 +437,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
19
]
}
@@ -398,11 +452,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
23
]
}
@@ -413,11 +467,11 @@
"span": {
"delete": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
22
]
}
@@ -428,11 +482,11 @@
"span": {
"delete": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
19
]
}
@@ -443,11 +497,11 @@
"span": {
"delete": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
23
]
}
@@ -458,11 +512,11 @@
"span": {
"insert": {
"start": [
- 6,
+ 4,
1
],
"end": [
- 6,
+ 4,
22
]
}
@@ -473,11 +527,11 @@
"span": {
"insert": {
"start": [
- 7,
+ 5,
1
],
"end": [
- 7,
+ 5,
19
]
}
@@ -488,11 +542,11 @@
"span": {
"insert": {
"start": [
- 8,
+ 6,
1
],
"end": [
- 8,
+ 6,
23
]
}
@@ -506,9 +560,27 @@
"filePaths": [
"variadic-function-declarations.go"
],
- "sha1": "5c6438d74774c5505b9710c5095be94697ab5fdc",
+ "patch": [
+ "diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
+ "index 1e4f816..99d1e54 100644",
+ "--- a/variadic-function-declarations.go",
+ "+++ b/variadic-function-declarations.go",
+ "@@ -1,9 +1,6 @@",
+ "-func g1(a ...*int) {}",
+ "-func g2(...int) {}",
+ "-func g3(a, ...bool) {}",
+ "-func f1(a ...*int) {}",
+ "-func f2(...int) {}",
+ "-func f3(a, ...bool) {}",
+ " func f1(a ...*int) {}",
+ " func f2(...int) {}",
+ " func f3(a, ...bool) {}",
+ "+func g1(a ...*int) {}",
+ "+func g2(...int) {}",
+ "+func g3(a, ...bool) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "e9c290c1f1bfc40557b2a947889eacec12be44fc"
+ "shas": "ffa8638d6bc29fe639cc3a3bdcb94d61b5c35336..724f49666d07410a3e8ec439bb133609ed92d2aa"
}
,{
"testCaseDescription": "go-variadic-function-declarations-delete-test",
@@ -519,11 +591,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -534,11 +606,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
19
]
}
@@ -549,11 +621,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
23
]
}
@@ -567,9 +639,21 @@
"filePaths": [
"variadic-function-declarations.go"
],
- "sha1": "e9c290c1f1bfc40557b2a947889eacec12be44fc",
+ "patch": [
+ "diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
+ "index 99d1e54..4a0a10b 100644",
+ "--- a/variadic-function-declarations.go",
+ "+++ b/variadic-function-declarations.go",
+ "@@ -1,6 +1,3 @@",
+ "-func f1(a ...*int) {}",
+ "-func f2(...int) {}",
+ "-func f3(a, ...bool) {}",
+ " func g1(a ...*int) {}",
+ " func g2(...int) {}",
+ " func g3(a, ...bool) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "f13f83e149b557f9ae2a7d43a03f1bfb49bbcedd"
+ "shas": "724f49666d07410a3e8ec439bb133609ed92d2aa..6d26c7b498f60c3ccc84002c96dc08b024d685c7"
}
,{
"testCaseDescription": "go-variadic-function-declarations-delete-rest-test",
@@ -580,11 +664,11 @@
"span": {
"delete": {
"start": [
- 3,
+ 1,
1
],
"end": [
- 3,
+ 1,
22
]
}
@@ -595,11 +679,11 @@
"span": {
"delete": {
"start": [
- 4,
+ 2,
1
],
"end": [
- 4,
+ 2,
19
]
}
@@ -610,11 +694,11 @@
"span": {
"delete": {
"start": [
- 5,
+ 3,
1
],
"end": [
- 5,
+ 3,
23
]
}
@@ -628,7 +712,16 @@
"filePaths": [
"variadic-function-declarations.go"
],
- "sha1": "f13f83e149b557f9ae2a7d43a03f1bfb49bbcedd",
+ "patch": [
+ "diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
+ "index 4a0a10b..e69de29 100644",
+ "--- a/variadic-function-declarations.go",
+ "+++ b/variadic-function-declarations.go",
+ "@@ -1,3 +0,0 @@",
+ "-func g1(a ...*int) {}",
+ "-func g2(...int) {}",
+ "-func g3(a, ...bool) {}"
+ ],
"gitDir": "test/corpus/repos/go",
- "sha2": "cbfe90e40b3f1a5f8f1a76f1e2b9dbebe28783ee"
+ "shas": "6d26c7b498f60c3ccc84002c96dc08b024d685c7..d533fb4333ed523cd36d6f2bb4f1c31eb61596f1"
}]
diff --git a/test/corpus/diff-summaries/javascript/anonymous-function.json b/test/corpus/diff-summaries/javascript/anonymous-function.json
index ab88c906f..dfe21d8a1 100644
--- a/test/corpus/diff-summaries/javascript/anonymous-function.json
+++ b/test/corpus/diff-summaries/javascript/anonymous-function.json
@@ -25,9 +25,16 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "c3ba4a1505773022c8c9750803b2f78c821f80a1",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index e69de29..b592868 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -0,0 +1 @@",
+ "+function(a,b) { return a + b; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b5bdaebe1a62c35afbab412c48b69be687db7d09"
+ "shas": "5f4dfa791577127cebc7f5fa8c7d94b7427980f3..2e9eda4d95ac6cbdd16de3ad1464523de63ffb44"
}
,{
"testCaseDescription": "javascript-anonymous-function-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "b5bdaebe1a62c35afbab412c48b69be687db7d09",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index b592868..e1de356 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1 +1,3 @@",
+ "+function(b,c) { return b * c; }",
+ "+function(a,b) { return a + b; }",
+ " function(a,b) { return a + b; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "79300c371f63ca7d92884cf2e4cb676518313a20"
+ "shas": "2e9eda4d95ac6cbdd16de3ad1464523de63ffb44..d6d789dd70b74b099621405aaab5cbb25e1a47eb"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-insert-test",
@@ -195,9 +211,19 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "79300c371f63ca7d92884cf2e4cb676518313a20",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index e1de356..4ca0d4c 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function(b,c) { return b * c; }",
+ "+function(a,b) { return a + b; }",
+ " function(a,b) { return a + b; }",
+ " function(a,b) { return a + b; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "016507d5f7e94b37702891fc7b0d62b850b6e225"
+ "shas": "d6d789dd70b74b099621405aaab5cbb25e1a47eb..d40be86ea2ce078c6a426ce0a8c252a71892113a"
}
,{
"testCaseDescription": "javascript-anonymous-function-replacement-test",
@@ -319,9 +345,19 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "016507d5f7e94b37702891fc7b0d62b850b6e225",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index 4ca0d4c..e1de356 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function(a,b) { return a + b; }",
+ "+function(b,c) { return b * c; }",
+ " function(a,b) { return a + b; }",
+ " function(a,b) { return a + b; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3fb4175329fcd15fec0bbc2fc1bf9180bdf4fbcd"
+ "shas": "d40be86ea2ce078c6a426ce0a8c252a71892113a..fbe8b2947cb17ec793516f3368dd2f787bccfe66"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-replacement-test",
@@ -380,9 +416,19 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "3fb4175329fcd15fec0bbc2fc1bf9180bdf4fbcd",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index e1de356..afdaccf 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function(b,c) { return b * c; }",
+ "-function(a,b) { return a + b; }",
+ " function(a,b) { return a + b; }",
+ "+function(b,c) { return b * c; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "690cd36fd94756b8e231d0e5134619fe533b1a87"
+ "shas": "fbe8b2947cb17ec793516f3368dd2f787bccfe66..260e74caf2632a2de525e1341d76ed31cc8cf2bf"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-test",
@@ -411,9 +457,17 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "690cd36fd94756b8e231d0e5134619fe533b1a87",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index afdaccf..9f1856f 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1,2 +1 @@",
+ "-function(a,b) { return a + b; }",
+ " function(b,c) { return b * c; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9b5d868b31faea679ddb9fe61b59042398eb187a"
+ "shas": "260e74caf2632a2de525e1341d76ed31cc8cf2bf..f425fbe0cbbd72279ea1a69e34baa8e341700a09"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-rest-test",
@@ -442,7 +496,14 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "9b5d868b31faea679ddb9fe61b59042398eb187a",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index 9f1856f..e69de29 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1 +0,0 @@",
+ "-function(b,c) { return b * c; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9fd0f7aee44dbf83b9a380bad5755081b4246e77"
+ "shas": "f425fbe0cbbd72279ea1a69e34baa8e341700a09..2a5f85a471c9c83f2e835139afa5eb7bfecd546a"
}]
diff --git a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json
index bec99d764..f9fe5f636 100644
--- a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json
+++ b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json
@@ -25,9 +25,16 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "9fd0f7aee44dbf83b9a380bad5755081b4246e77",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index e69de29..4a26ae8 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -0,0 +1 @@",
+ "+function() { return 'hi'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3f71749ad94ee55259b0185c358235d8ac903467"
+ "shas": "2a5f85a471c9c83f2e835139afa5eb7bfecd546a..a2527ab39dbaa7651e66e24f3d143d11060841f6"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "3f71749ad94ee55259b0185c358235d8ac903467",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index 4a26ae8..c31dd4b 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1 +1,3 @@",
+ "+function() { return 'hello'; }",
+ "+function() { return 'hi'; }",
+ " function() { return 'hi'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0863179c63f1167cdfb18c909a4085cc496937f6"
+ "shas": "a2527ab39dbaa7651e66e24f3d143d11060841f6..4b3321e8a707ad91af6735319257f7f68fb593b7"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "0863179c63f1167cdfb18c909a4085cc496937f6",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index c31dd4b..6b1efa4 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function() { return 'hello'; }",
+ "+function() { return 'hi'; }",
+ " function() { return 'hi'; }",
+ " function() { return 'hi'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "694e7e4dbf661db0da87a68db68975fe34fdba3f"
+ "shas": "4b3321e8a707ad91af6735319257f7f68fb593b7..a01626612654464812b9cedaad745f686edc8138"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "694e7e4dbf661db0da87a68db68975fe34fdba3f",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index 6b1efa4..c31dd4b 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function() { return 'hi'; }",
+ "+function() { return 'hello'; }",
+ " function() { return 'hi'; }",
+ " function() { return 'hi'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "353eeb99fc286d0683f1d698a8f6212ce4699acd"
+ "shas": "a01626612654464812b9cedaad745f686edc8138..d640dfcedbbda8708bb8c679b2b96460e63e8e53"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "353eeb99fc286d0683f1d698a8f6212ce4699acd",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index c31dd4b..b8e05c0 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function() { return 'hello'; }",
+ "-function() { return 'hi'; }",
+ " function() { return 'hi'; }",
+ "+function() { return 'hello'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9862380b35add3763257a9f558bf4ff02427d9cf"
+ "shas": "d640dfcedbbda8708bb8c679b2b96460e63e8e53..f1436a17d64c050a7d6aa15fe0876ce3fc4176f0"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "9862380b35add3763257a9f558bf4ff02427d9cf",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index b8e05c0..ce1ef83 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1,2 +1 @@",
+ "-function() { return 'hi'; }",
+ " function() { return 'hello'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e42905606a9100ef0e06cb728b265e6d772e9a9f"
+ "shas": "f1436a17d64c050a7d6aa15fe0876ce3fc4176f0..1bd2372f874ec3588d5510b5c7fa50c378b5e665"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "e42905606a9100ef0e06cb728b265e6d772e9a9f",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index ce1ef83..e69de29 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1 +0,0 @@",
+ "-function() { return 'hello'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8662f58f1d7ce21fddcefecae990742a5d1398dc"
+ "shas": "1bd2372f874ec3588d5510b5c7fa50c378b5e665..e66b1b20abc596d2b560eaa80f1749c79816f9ff"
}]
diff --git a/test/corpus/diff-summaries/javascript/array.json b/test/corpus/diff-summaries/javascript/array.json
index 90f2a1923..335364806 100644
--- a/test/corpus/diff-summaries/javascript/array.json
+++ b/test/corpus/diff-summaries/javascript/array.json
@@ -25,9 +25,16 @@
"filePaths": [
"array.js"
],
- "sha1": "9ccab273233837d842e68ec909416aab24ff359a",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index e69de29..3335582 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -0,0 +1 @@",
+ "+[ \"item1\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b653c66def8445f3ba4880fee2c049196d273774"
+ "shas": "654a538b26c9b4c8637e6c2e4cd497c93e690310..cbf013688399920af101ea056e9fba5ecba0601d"
}
,{
"testCaseDescription": "javascript-array-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"array.js"
],
- "sha1": "b653c66def8445f3ba4880fee2c049196d273774",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index 3335582..cf37d7c 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1 +1,3 @@",
+ "+[ \"item1\", \"item2\" ];",
+ "+[ \"item1\" ];",
+ " [ \"item1\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c055d2c11306c9f9cbb2ed0d9f0b638b953f7b4a"
+ "shas": "cbf013688399920af101ea056e9fba5ecba0601d..87e3b9ed3c5f26c596ad2b5da90359174c84f53c"
}
,{
"testCaseDescription": "javascript-array-delete-insert-test",
@@ -102,9 +118,19 @@
"filePaths": [
"array.js"
],
- "sha1": "c055d2c11306c9f9cbb2ed0d9f0b638b953f7b4a",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index cf37d7c..c2cb17f 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1,3 +1,3 @@",
+ "-[ \"item1\", \"item2\" ];",
+ "+[ \"item1\" ];",
+ " [ \"item1\" ];",
+ " [ \"item1\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "074894088cf9d55ae3bcdbb3a8e4270b8d2a0c26"
+ "shas": "87e3b9ed3c5f26c596ad2b5da90359174c84f53c..ea49177e8ff82b772f7347682975cb1fa5e7b012"
}
,{
"testCaseDescription": "javascript-array-replacement-test",
@@ -133,9 +159,19 @@
"filePaths": [
"array.js"
],
- "sha1": "074894088cf9d55ae3bcdbb3a8e4270b8d2a0c26",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index c2cb17f..cf37d7c 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1,3 +1,3 @@",
+ "-[ \"item1\" ];",
+ "+[ \"item1\", \"item2\" ];",
+ " [ \"item1\" ];",
+ " [ \"item1\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7e646e80e9fabf33c78eca4122ac60e146b52423"
+ "shas": "ea49177e8ff82b772f7347682975cb1fa5e7b012..1e28fd793a6ab61ed59b28d8ee56b55be7ad79ec"
}
,{
"testCaseDescription": "javascript-array-delete-replacement-test",
@@ -194,9 +230,19 @@
"filePaths": [
"array.js"
],
- "sha1": "7e646e80e9fabf33c78eca4122ac60e146b52423",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index cf37d7c..a4d92b8 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1,3 +1,2 @@",
+ "-[ \"item1\", \"item2\" ];",
+ "-[ \"item1\" ];",
+ " [ \"item1\" ];",
+ "+[ \"item1\", \"item2\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c61cc49cb2088ca7e12614a4b31e181f5a0e97d6"
+ "shas": "1e28fd793a6ab61ed59b28d8ee56b55be7ad79ec..fdc62b5a013932e082ba61a576b8fb54cd1d0791"
}
,{
"testCaseDescription": "javascript-array-delete-test",
@@ -225,9 +271,17 @@
"filePaths": [
"array.js"
],
- "sha1": "c61cc49cb2088ca7e12614a4b31e181f5a0e97d6",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index a4d92b8..7f2f50e 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1,2 +1 @@",
+ "-[ \"item1\" ];",
+ " [ \"item1\", \"item2\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9601453a391957f917ee112f1e6abce225b21bac"
+ "shas": "fdc62b5a013932e082ba61a576b8fb54cd1d0791..9e91959fe3d3ec022474f242a8456b900fdfd8d2"
}
,{
"testCaseDescription": "javascript-array-delete-rest-test",
@@ -256,7 +310,14 @@
"filePaths": [
"array.js"
],
- "sha1": "9601453a391957f917ee112f1e6abce225b21bac",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index 7f2f50e..e69de29 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1 +0,0 @@",
+ "-[ \"item1\", \"item2\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e1f7c5a495d4e15d24ac325f6dec565f21f021e8"
+ "shas": "9e91959fe3d3ec022474f242a8456b900fdfd8d2..0bdf412036a9a6aea51108a20404c37541fffcfb"
}]
diff --git a/test/corpus/diff-summaries/javascript/arrow-function.json b/test/corpus/diff-summaries/javascript/arrow-function.json
index a9abec708..bd768fce5 100644
--- a/test/corpus/diff-summaries/javascript/arrow-function.json
+++ b/test/corpus/diff-summaries/javascript/arrow-function.json
@@ -25,9 +25,16 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "1a65f6b31571ca180a7067af4efe0b804b5bd17f",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index e69de29..9ef167c 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -0,0 +1 @@",
+ "+(f, g) => { return h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d8b95c6c259bbc1031068e76b71ee165a32fcc90"
+ "shas": "d700dc51fee7a3dd557906dcdf46d426285d7955..edda3c60ac532d534d84539648fa827ff18a6c59"
}
,{
"testCaseDescription": "javascript-arrow-function-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "d8b95c6c259bbc1031068e76b71ee165a32fcc90",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index 9ef167c..92dea6f 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1 +1,3 @@",
+ "+(f, g) => { return g; };",
+ "+(f, g) => { return h; };",
+ " (f, g) => { return h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "38971f3bb12072ce71a8af2e61b40128e2e04335"
+ "shas": "edda3c60ac532d534d84539648fa827ff18a6c59..63fd87f8cafc4a46f2927f9825cc20e5f116a093"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "38971f3bb12072ce71a8af2e61b40128e2e04335",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index 92dea6f..8f5bb51 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-(f, g) => { return g; };",
+ "+(f, g) => { return h; };",
+ " (f, g) => { return h; };",
+ " (f, g) => { return h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0bad91b1393996893c42c7ca6cea6b485ed79f3d"
+ "shas": "63fd87f8cafc4a46f2927f9825cc20e5f116a093..29b18be738dde19aa61343c5f4e54bf83f4b30ea"
}
,{
"testCaseDescription": "javascript-arrow-function-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "0bad91b1393996893c42c7ca6cea6b485ed79f3d",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index 8f5bb51..92dea6f 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-(f, g) => { return h; };",
+ "+(f, g) => { return g; };",
+ " (f, g) => { return h; };",
+ " (f, g) => { return h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "22eb88fd92a0f54db863a2c99e7f6cefd573d70c"
+ "shas": "29b18be738dde19aa61343c5f4e54bf83f4b30ea..d92f900ef9873f273da632ea9c54adcd7acc7961"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "22eb88fd92a0f54db863a2c99e7f6cefd573d70c",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index 92dea6f..acab9a9 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-(f, g) => { return g; };",
+ "-(f, g) => { return h; };",
+ " (f, g) => { return h; };",
+ "+(f, g) => { return g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ce32c18979a6f118f1a64d68058aea090fbd6ffa"
+ "shas": "d92f900ef9873f273da632ea9c54adcd7acc7961..243f2be7291992566bd0ab2c2caef9e7ac13e02d"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "ce32c18979a6f118f1a64d68058aea090fbd6ffa",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index acab9a9..ef1be25 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1,2 +1 @@",
+ "-(f, g) => { return h; };",
+ " (f, g) => { return g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "555a09419c1aeebf5676d25753625cc4a6558f9b"
+ "shas": "243f2be7291992566bd0ab2c2caef9e7ac13e02d..3128237c6d11459cf7d3e9add902e7be8d38710b"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "555a09419c1aeebf5676d25753625cc4a6558f9b",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index ef1be25..e69de29 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1 +0,0 @@",
+ "-(f, g) => { return g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "843b9d83e2acc3f1bf014abc4e2402e1a783d3f6"
+ "shas": "3128237c6d11459cf7d3e9add902e7be8d38710b..5cab8720cde055f6d78f5c5deaf8980b89a434e1"
}]
diff --git a/test/corpus/diff-summaries/javascript/assignment.json b/test/corpus/diff-summaries/javascript/assignment.json
index 482c06610..66519160d 100644
--- a/test/corpus/diff-summaries/javascript/assignment.json
+++ b/test/corpus/diff-summaries/javascript/assignment.json
@@ -25,9 +25,16 @@
"filePaths": [
"assignment.js"
],
- "sha1": "f5dfc0945ffae36e0f9784dcfeb8472344055afc",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index e69de29..6882fe5 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -0,0 +1 @@",
+ "+x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6fc2b9a8bdab5a87aeb8214b88ddafb278098394"
+ "shas": "10c888c0caabf36cb211a96640afbe435dfad3fb..6a5eb86577a86881fdd53c3db17dd589617b887e"
}
,{
"testCaseDescription": "javascript-assignment-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"assignment.js"
],
- "sha1": "6fc2b9a8bdab5a87aeb8214b88ddafb278098394",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index 6882fe5..fb4cba4 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1 +1,3 @@",
+ "+x = 1;",
+ "+x = 0;",
+ " x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "45ee00517df6dd2f5c12523b82f4ae9c361cbbab"
+ "shas": "6a5eb86577a86881fdd53c3db17dd589617b887e..79ca8610276bd0cc32d257702e20ec268187f1b6"
}
,{
"testCaseDescription": "javascript-assignment-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"assignment.js"
],
- "sha1": "45ee00517df6dd2f5c12523b82f4ae9c361cbbab",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index fb4cba4..42e16c6 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-x = 1;",
+ "+x = 0;",
+ " x = 0;",
+ " x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c68a9ee4c0811ebc8bc6a97087ad578bda055575"
+ "shas": "79ca8610276bd0cc32d257702e20ec268187f1b6..c3da25392def8e82aaf0179cdd8cc51849d805c8"
}
,{
"testCaseDescription": "javascript-assignment-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"assignment.js"
],
- "sha1": "c68a9ee4c0811ebc8bc6a97087ad578bda055575",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index 42e16c6..fb4cba4 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-x = 0;",
+ "+x = 1;",
+ " x = 0;",
+ " x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "aa18ede37e29b97d5478771c02f899c26ed29ec8"
+ "shas": "c3da25392def8e82aaf0179cdd8cc51849d805c8..be4979757f9464e59b4b7fb7dbdce17f4f362029"
}
,{
"testCaseDescription": "javascript-assignment-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"assignment.js"
],
- "sha1": "aa18ede37e29b97d5478771c02f899c26ed29ec8",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index fb4cba4..11fe15d 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1,3 +1,2 @@",
+ "-x = 1;",
+ "-x = 0;",
+ " x = 0;",
+ "+x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e34fae4bc40de3527a8af142718f5034b8c89464"
+ "shas": "be4979757f9464e59b4b7fb7dbdce17f4f362029..592d4d9a24fe20282bbaa1cf66bbe20959d47ae5"
}
,{
"testCaseDescription": "javascript-assignment-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"assignment.js"
],
- "sha1": "e34fae4bc40de3527a8af142718f5034b8c89464",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index 11fe15d..198b8f8 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1,2 +1 @@",
+ "-x = 0;",
+ " x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "844f1b80889b328b7de377506a20fd1e07722c3c"
+ "shas": "592d4d9a24fe20282bbaa1cf66bbe20959d47ae5..f0b77709f5be6c1d671a943d73b8fbb12344762e"
}
,{
"testCaseDescription": "javascript-assignment-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"assignment.js"
],
- "sha1": "844f1b80889b328b7de377506a20fd1e07722c3c",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index 198b8f8..e69de29 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1 +0,0 @@",
+ "-x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "45a5360969a82ef1602c4fd2629a242bd75a1edf"
+ "shas": "f0b77709f5be6c1d671a943d73b8fbb12344762e..83f3153b76f49e077237997c965dc6f3c3a159bc"
}]
diff --git a/test/corpus/diff-summaries/javascript/bitwise-operator.json b/test/corpus/diff-summaries/javascript/bitwise-operator.json
index e2af37a81..af2ae33cd 100644
--- a/test/corpus/diff-summaries/javascript/bitwise-operator.json
+++ b/test/corpus/diff-summaries/javascript/bitwise-operator.json
@@ -25,9 +25,16 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "761fc16b7840013a3a30a594193222af2c710535",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index e69de29..021cf6a 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -0,0 +1 @@",
+ "+i >> j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ae0665071ff8d408f9dba2bc188c7ee5e6d72c8e"
+ "shas": "5edf134e2ccb0fa1cd27b2e07b4279575f1a5f0d..e2e6f5b9a61fa806befb17711cf3ae52dd20f725"
}
,{
"testCaseDescription": "javascript-bitwise-operator-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "ae0665071ff8d408f9dba2bc188c7ee5e6d72c8e",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index 021cf6a..3e0b6c1 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1 +1,3 @@",
+ "+i >> k;",
+ "+i >> j;",
+ " i >> j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "30a3708b6b22a2fecb6a2e10ac27b6945a87f9f7"
+ "shas": "e2e6f5b9a61fa806befb17711cf3ae52dd20f725..de455af0e3ab990d8f20a4555d4bf28324551ed0"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "30a3708b6b22a2fecb6a2e10ac27b6945a87f9f7",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index 3e0b6c1..18853d1 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i >> k;",
+ "+i >> j;",
+ " i >> j;",
+ " i >> j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b5a0645c9262b7ef092240be639ac5cf0758cf64"
+ "shas": "de455af0e3ab990d8f20a4555d4bf28324551ed0..59f5fd5cc14501c063c3ec3b9563503a4f22537b"
}
,{
"testCaseDescription": "javascript-bitwise-operator-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "b5a0645c9262b7ef092240be639ac5cf0758cf64",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index 18853d1..3e0b6c1 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i >> j;",
+ "+i >> k;",
+ " i >> j;",
+ " i >> j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d2dc484eb040a787945e88294a926f120fed4e12"
+ "shas": "59f5fd5cc14501c063c3ec3b9563503a4f22537b..24328d0f069d5e61a5926bedf6e0a074361d7477"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "d2dc484eb040a787945e88294a926f120fed4e12",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index 3e0b6c1..ee7d8de 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-i >> k;",
+ "-i >> j;",
+ " i >> j;",
+ "+i >> k;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8411bfe78b348cf56e382a55f6c1bd8541bda049"
+ "shas": "24328d0f069d5e61a5926bedf6e0a074361d7477..083807f60ce4fd39ee7612cb97e2dc2351a09203"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "8411bfe78b348cf56e382a55f6c1bd8541bda049",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index ee7d8de..2800c8c 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1,2 +1 @@",
+ "-i >> j;",
+ " i >> k;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "12c46cd84849f5766fff9bdf00c5b8357667c02b"
+ "shas": "083807f60ce4fd39ee7612cb97e2dc2351a09203..1bceab9d521db6e74ccfca50dae11d9ac030a4bc"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "12c46cd84849f5766fff9bdf00c5b8357667c02b",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index 2800c8c..e69de29 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1 +0,0 @@",
+ "-i >> k;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "149d0a9500261cd37b696c4ab2527d34f0133522"
+ "shas": "1bceab9d521db6e74ccfca50dae11d9ac030a4bc..4e47562dd59646a6c6c55ab138660495394bc5c9"
}]
diff --git a/test/corpus/diff-summaries/javascript/boolean-operator.json b/test/corpus/diff-summaries/javascript/boolean-operator.json
index 0e8d99906..9b6884552 100644
--- a/test/corpus/diff-summaries/javascript/boolean-operator.json
+++ b/test/corpus/diff-summaries/javascript/boolean-operator.json
@@ -25,9 +25,16 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "0f277a98ca88f6c1e02d2811fa15b32c1909edf0",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index e69de29..7280a98 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -0,0 +1 @@",
+ "+i || j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d039a78308a35a509cecb57ba239162e939925ae"
+ "shas": "69248e3fdb3e6ab7da864ef7bd3a915aeefd3cc4..697a361cfb8bcfd14631209deb6159679d166115"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "d039a78308a35a509cecb57ba239162e939925ae",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index 7280a98..fe3f306 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1 +1,3 @@",
+ "+i && j;",
+ "+i || j;",
+ " i || j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9f2ce7d364ba8f68e4aaf3f2a1bc525afb0fbcfc"
+ "shas": "697a361cfb8bcfd14631209deb6159679d166115..2829490ad0cdc2f954145a2698444d5daf1da199"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-insert-test",
@@ -84,9 +100,19 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "9f2ce7d364ba8f68e4aaf3f2a1bc525afb0fbcfc",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index fe3f306..273c0ee 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i && j;",
+ "+i || j;",
+ " i || j;",
+ " i || j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9f9d0f34d19c5335218140e896e56cca5483085c"
+ "shas": "2829490ad0cdc2f954145a2698444d5daf1da199..8a66944201f7ad0fc2ee8fcdcaff607125c8cc0f"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-test",
@@ -97,9 +123,19 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "9f9d0f34d19c5335218140e896e56cca5483085c",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index 273c0ee..fe3f306 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i || j;",
+ "+i && j;",
+ " i || j;",
+ " i || j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b7735561df1e286eb16fbd6d6f12c40f33f0d884"
+ "shas": "8a66944201f7ad0fc2ee8fcdcaff607125c8cc0f..0658cb117a6a6719f8464948c86e3e278d8c2a95"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-replacement-test",
@@ -128,9 +164,19 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "b7735561df1e286eb16fbd6d6f12c40f33f0d884",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index fe3f306..7f4873c 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-i && j;",
+ "-i || j;",
+ " i || j;",
+ "+i && j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4209ac85ff7d9fdbe9ac2d309fefec0af45d0702"
+ "shas": "0658cb117a6a6719f8464948c86e3e278d8c2a95..35f6d8f480c9f8645a3c0d8f9fa5339059a6380a"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-test",
@@ -159,9 +205,17 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "4209ac85ff7d9fdbe9ac2d309fefec0af45d0702",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index 7f4873c..c6921d1 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1,2 +1 @@",
+ "-i || j;",
+ " i && j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2ee56bee510724715c14244f51c38c55b13ed274"
+ "shas": "35f6d8f480c9f8645a3c0d8f9fa5339059a6380a..2b07585de8be3e4334361368f2dc465278842434"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-rest-test",
@@ -190,7 +244,14 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "2ee56bee510724715c14244f51c38c55b13ed274",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index c6921d1..e69de29 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1 +0,0 @@",
+ "-i && j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "761fc16b7840013a3a30a594193222af2c710535"
+ "shas": "2b07585de8be3e4334361368f2dc465278842434..5edf134e2ccb0fa1cd27b2e07b4279575f1a5f0d"
}]
diff --git a/test/corpus/diff-summaries/javascript/chained-callbacks.json b/test/corpus/diff-summaries/javascript/chained-callbacks.json
index 5755f0f51..253a7cb57 100644
--- a/test/corpus/diff-summaries/javascript/chained-callbacks.json
+++ b/test/corpus/diff-summaries/javascript/chained-callbacks.json
@@ -25,9 +25,16 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "0dd5a42b7e992a63ee0e46bbbc58699dd09f6851",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index e69de29..ce9ee1e 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -0,0 +1 @@",
+ "+this.map(function (a) { return a.b; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5a141e4ade0038fbde994ab77049a38a1565b976"
+ "shas": "1512ae1cef2a096ce2723ce98334e4ce0e4bc82b..2a014ee8fd6ea4f8ce5b6bae0ca35a4fa6462deb"
}
,{
"testCaseDescription": "javascript-chained-callbacks-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "5a141e4ade0038fbde994ab77049a38a1565b976",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index ce9ee1e..acba744 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1 +1,3 @@",
+ "+this.reduce(function (a) { return b.a; })",
+ "+this.map(function (a) { return a.b; })",
+ " this.map(function (a) { return a.b; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8bb88ee35fe50732fa664a022dab4f67d4fad2a3"
+ "shas": "2a014ee8fd6ea4f8ce5b6bae0ca35a4fa6462deb..6a6e1ae99abc9cae5f8ac31aac43836380944603"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-insert-test",
@@ -168,9 +184,19 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "8bb88ee35fe50732fa664a022dab4f67d4fad2a3",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index acba744..7390534 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1,3 +1,3 @@",
+ "-this.reduce(function (a) { return b.a; })",
+ "+this.map(function (a) { return a.b; })",
+ " this.map(function (a) { return a.b; })",
+ " this.map(function (a) { return a.b; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "20f50a2164ac72df558b6ba29253a750d0e43b30"
+ "shas": "6a6e1ae99abc9cae5f8ac31aac43836380944603..c86429cb689c74e2ce3988c8bc257a365734cbe3"
}
,{
"testCaseDescription": "javascript-chained-callbacks-replacement-test",
@@ -265,9 +291,19 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "20f50a2164ac72df558b6ba29253a750d0e43b30",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index 7390534..acba744 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1,3 +1,3 @@",
+ "-this.map(function (a) { return a.b; })",
+ "+this.reduce(function (a) { return b.a; })",
+ " this.map(function (a) { return a.b; })",
+ " this.map(function (a) { return a.b; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0df44200409e2bc7040f464d19c0105073aa8e0a"
+ "shas": "c86429cb689c74e2ce3988c8bc257a365734cbe3..c4df0b8afdd73cae6d89a9098ae38d9c3085dbb8"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-replacement-test",
@@ -326,9 +362,19 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "0df44200409e2bc7040f464d19c0105073aa8e0a",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index acba744..c4db432 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1,3 +1,2 @@",
+ "-this.reduce(function (a) { return b.a; })",
+ "-this.map(function (a) { return a.b; })",
+ " this.map(function (a) { return a.b; })",
+ "+this.reduce(function (a) { return b.a; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7e75f5dee9344c80bf09a677752c16c9ca0ee945"
+ "shas": "c4df0b8afdd73cae6d89a9098ae38d9c3085dbb8..8b7dbbb0ca20e47dfed24fb3eb3a790721d2e9d0"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-test",
@@ -357,9 +403,17 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "7e75f5dee9344c80bf09a677752c16c9ca0ee945",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index c4db432..e593419 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1,2 +1 @@",
+ "-this.map(function (a) { return a.b; })",
+ " this.reduce(function (a) { return b.a; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0313d7b16c660931a9fcba9a02f3f79dcb16ad95"
+ "shas": "8b7dbbb0ca20e47dfed24fb3eb3a790721d2e9d0..e2c2e86db834a0ab3c6006c6385e90d780851357"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-rest-test",
@@ -388,7 +442,14 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "0313d7b16c660931a9fcba9a02f3f79dcb16ad95",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index e593419..e69de29 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1 +0,0 @@",
+ "-this.reduce(function (a) { return b.a; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1a9472e94c365639f5f2b5c519a06c2daf17c630"
+ "shas": "e2c2e86db834a0ab3c6006c6385e90d780851357..5ef42771e35b5af39f3befe137fedf40f174a5c7"
}]
diff --git a/test/corpus/diff-summaries/javascript/chained-property-access.json b/test/corpus/diff-summaries/javascript/chained-property-access.json
index 2a20eb690..7c4d6aad9 100644
--- a/test/corpus/diff-summaries/javascript/chained-property-access.json
+++ b/test/corpus/diff-summaries/javascript/chained-property-access.json
@@ -25,9 +25,16 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "d634acd5aed3ab7ef4a9914234758a3bf356d2c4",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index e69de29..5914a55 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -0,0 +1 @@",
+ "+return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "723940f8df7814d9f0fb1ea03dddbff771d80ac8"
+ "shas": "71feda9fd80ab60adab5cf81748710b2a610173f..02c42e637780aeb5874c5f740ba764a0b606d950"
}
,{
"testCaseDescription": "javascript-chained-property-access-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "723940f8df7814d9f0fb1ea03dddbff771d80ac8",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 5914a55..7095976 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1 +1,3 @@",
+ "+return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
+ "+return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4d9c7053f056b963074f086d40020195bff90c32"
+ "shas": "02c42e637780aeb5874c5f740ba764a0b606d950..eb64ebf3bc9351da0d4cbb59cdfc44d7152b090e"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-insert-test",
@@ -141,9 +157,19 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "4d9c7053f056b963074f086d40020195bff90c32",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 7095976..98df938 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1,3 +1,3 @@",
+ "-return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
+ "+return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b0faefc21e5b571d399056063f96cfbf810a503f"
+ "shas": "eb64ebf3bc9351da0d4cbb59cdfc44d7152b090e..d87ef7df3e23f3b4837c9dd09aeca869774aa731"
}
,{
"testCaseDescription": "javascript-chained-property-access-replacement-test",
@@ -211,9 +237,19 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "b0faefc21e5b571d399056063f96cfbf810a503f",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 98df938..7095976 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1,3 +1,3 @@",
+ "-return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ "+return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ea742ea1e997a7a1241d1e719c3b313d8a42067c"
+ "shas": "d87ef7df3e23f3b4837c9dd09aeca869774aa731..2e00036e857c5aa6af0eb4ab23bd4cbb28bd90a2"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-replacement-test",
@@ -272,9 +308,19 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "ea742ea1e997a7a1241d1e719c3b313d8a42067c",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 7095976..7b764ca 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1,3 +1,2 @@",
+ "-return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
+ "-return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ "+return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5517a9b89409234d2dc3cbf17aa526d72bc12479"
+ "shas": "2e00036e857c5aa6af0eb4ab23bd4cbb28bd90a2..5eb335f13f0dea85c75b4d5f174832b08af8a0e6"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-test",
@@ -303,9 +349,17 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "5517a9b89409234d2dc3cbf17aa526d72bc12479",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 7b764ca..5d6d3a0 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1,2 +1 @@",
+ "-return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "66cacfd430f02a62b6976e31fdc0a53ae019dd5e"
+ "shas": "5eb335f13f0dea85c75b4d5f174832b08af8a0e6..054acb661f91e8a5b9096d552c5b3410bacc4811"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-rest-test",
@@ -334,7 +388,14 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "66cacfd430f02a62b6976e31fdc0a53ae019dd5e",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 5d6d3a0..e69de29 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1 +0,0 @@",
+ "-return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0dd5a42b7e992a63ee0e46bbbc58699dd09f6851"
+ "shas": "054acb661f91e8a5b9096d552c5b3410bacc4811..1512ae1cef2a096ce2723ce98334e4ce0e4bc82b"
}]
diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json
index d9ab434e1..ab4c4cfe2 100644
--- a/test/corpus/diff-summaries/javascript/class.json
+++ b/test/corpus/diff-summaries/javascript/class.json
@@ -25,9 +25,16 @@
"filePaths": [
"class.js"
],
- "sha1": "559546b09a86fffc79e8283d8f7567d491c07e90",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index e69de29..8f6ae64 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -0,0 +1 @@",
+ "+class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0ac57022cf74cb78426a1df060ce3ac2ff83cd71"
+ "shas": "f6dfeb42af9db740677fd60341ea39da711f7c81..f071d25d12bb0086a285449efbe5cfaeeed8e436"
}
,{
"testCaseDescription": "javascript-class-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"class.js"
],
- "sha1": "0ac57022cf74cb78426a1df060ce3ac2ff83cd71",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index 8f6ae64..b509437 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1 +1,3 @@",
+ "+class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
+ "+class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5bbc894719630d0236a85728f425e98a4ef3487b"
+ "shas": "f071d25d12bb0086a285449efbe5cfaeeed8e436..ba736a07888eb4991323c035f2bf78fe1650ea56"
}
,{
"testCaseDescription": "javascript-class-delete-insert-test",
@@ -105,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'foo' identifier with the 'one' identifier in the one method of the 'Foo' class"
+ "summary": "Replaced the 'foo' identifier with the 'one' identifier in the 'one(a)' method of the 'Foo' class"
},
{
"span": {
@@ -120,7 +136,7 @@
]
}
},
- "summary": "Added the 'two' method in the Foo class"
+ "summary": "Added the 'two(b)' method in the Foo class"
},
{
"span": {
@@ -135,7 +151,7 @@
]
}
},
- "summary": "Added the 'three' method in the Foo class"
+ "summary": "Added the 'three(c)' method in the Foo class"
},
{
"span": {
@@ -150,7 +166,7 @@
]
}
},
- "summary": "Deleted the 'bar' method in the Foo class"
+ "summary": "Deleted the 'bar(b)' method in the Foo class"
},
{
"span": {
@@ -165,7 +181,7 @@
]
}
},
- "summary": "Deleted the 'baz' method in the Foo class"
+ "summary": "Deleted the 'baz(c)' method in the Foo class"
}
]
},
@@ -174,9 +190,19 @@
"filePaths": [
"class.js"
],
- "sha1": "5bbc894719630d0236a85728f425e98a4ef3487b",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index b509437..c4f5c91 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1,3 +1,3 @@",
+ "-class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
+ "+class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7e7e2be0141ca3710f3a774caa03f4704e9d3586"
+ "shas": "ba736a07888eb4991323c035f2bf78fe1650ea56..c99d7b8dc9cff808ef1e6010caa4573ad1694d9b"
}
,{
"testCaseDescription": "javascript-class-replacement-test",
@@ -208,7 +234,7 @@
}
]
},
- "summary": "Replaced the 'one' identifier with the 'foo' identifier in the foo method of the 'Foo' class"
+ "summary": "Replaced the 'one' identifier with the 'foo' identifier in the 'foo(a)' method of the 'Foo' class"
},
{
"span": {
@@ -223,7 +249,7 @@
]
}
},
- "summary": "Added the 'bar' method in the Foo class"
+ "summary": "Added the 'bar(b)' method in the Foo class"
},
{
"span": {
@@ -238,7 +264,7 @@
]
}
},
- "summary": "Added the 'baz' method in the Foo class"
+ "summary": "Added the 'baz(c)' method in the Foo class"
},
{
"span": {
@@ -253,7 +279,7 @@
]
}
},
- "summary": "Deleted the 'two' method in the Foo class"
+ "summary": "Deleted the 'two(b)' method in the Foo class"
},
{
"span": {
@@ -268,7 +294,7 @@
]
}
},
- "summary": "Deleted the 'three' method in the Foo class"
+ "summary": "Deleted the 'three(c)' method in the Foo class"
}
]
},
@@ -277,9 +303,19 @@
"filePaths": [
"class.js"
],
- "sha1": "7e7e2be0141ca3710f3a774caa03f4704e9d3586",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index c4f5c91..b509437 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1,3 +1,3 @@",
+ "-class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ "+class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f67a4f59fd14475400023beebe947c59aea5f3ea"
+ "shas": "c99d7b8dc9cff808ef1e6010caa4573ad1694d9b..75a0caa880f62a0706ff723f555a9ec1f0c53c29"
}
,{
"testCaseDescription": "javascript-class-delete-replacement-test",
@@ -338,9 +374,19 @@
"filePaths": [
"class.js"
],
- "sha1": "f67a4f59fd14475400023beebe947c59aea5f3ea",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index b509437..b1ef404 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1,3 +1,2 @@",
+ "-class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
+ "-class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ "+class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ef1f76b5f01fce4b330b99a4ebf3b128c03b7cb1"
+ "shas": "75a0caa880f62a0706ff723f555a9ec1f0c53c29..4231a3b306d145aa37ceb879ef6f8da6221e54b8"
}
,{
"testCaseDescription": "javascript-class-delete-test",
@@ -369,9 +415,17 @@
"filePaths": [
"class.js"
],
- "sha1": "ef1f76b5f01fce4b330b99a4ebf3b128c03b7cb1",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index b1ef404..2c17f72 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1,2 +1 @@",
+ "-class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "db58ab719fe45f004df748e0e6248d756f7ad9f3"
+ "shas": "4231a3b306d145aa37ceb879ef6f8da6221e54b8..d5627235989da4028cfcb15c4b1ee2bdc544fd31"
}
,{
"testCaseDescription": "javascript-class-delete-rest-test",
@@ -400,7 +454,14 @@
"filePaths": [
"class.js"
],
- "sha1": "db58ab719fe45f004df748e0e6248d756f7ad9f3",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index 2c17f72..e69de29 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1 +0,0 @@",
+ "-class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9ccab273233837d842e68ec909416aab24ff359a"
+ "shas": "d5627235989da4028cfcb15c4b1ee2bdc544fd31..654a538b26c9b4c8637e6c2e4cd497c93e690310"
}]
diff --git a/test/corpus/diff-summaries/javascript/comma-operator.json b/test/corpus/diff-summaries/javascript/comma-operator.json
index 0a09ac58e..66a418dab 100644
--- a/test/corpus/diff-summaries/javascript/comma-operator.json
+++ b/test/corpus/diff-summaries/javascript/comma-operator.json
@@ -40,9 +40,16 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "653a2a2b908c1963d4682a6e4b6e89f1aa17b275",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index e69de29..cff019f 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -0,0 +1 @@",
+ "+a = 1, b = 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7d8c6c9fdcb9ab7e9f40ae14efc813ae2b67e19e"
+ "shas": "ec86aaba01801d01aca70fd31403642be1e2d438..b0a5f928a8a4594bb176a56275c43ccab6e2e2a0"
}
,{
"testCaseDescription": "javascript-comma-operator-replacement-insert-test",
@@ -101,9 +108,18 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "7d8c6c9fdcb9ab7e9f40ae14efc813ae2b67e19e",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index cff019f..93ece10 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1 +1,3 @@",
+ "+c = {d: (3, 4 + 5, 6)};",
+ "+a = 1, b = 2;",
+ " a = 1, b = 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "40847aa7f589fd835e91320d43628d16fd37ef15"
+ "shas": "b0a5f928a8a4594bb176a56275c43ccab6e2e2a0..315b46ccdb9a45c374b4ed1cc51a062d74c13a78"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-insert-test",
@@ -162,9 +178,19 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "40847aa7f589fd835e91320d43628d16fd37ef15",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index 93ece10..f738c2d 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-c = {d: (3, 4 + 5, 6)};",
+ "+a = 1, b = 2;",
+ " a = 1, b = 2;",
+ " a = 1, b = 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b244fddf952c3cadad8f104cc2ee2abbf93dafcf"
+ "shas": "315b46ccdb9a45c374b4ed1cc51a062d74c13a78..30cf69eb0cc5543fe53be82f29cd0e0371e30cd1"
}
,{
"testCaseDescription": "javascript-comma-operator-replacement-test",
@@ -223,9 +249,19 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "b244fddf952c3cadad8f104cc2ee2abbf93dafcf",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index f738c2d..93ece10 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-a = 1, b = 2;",
+ "+c = {d: (3, 4 + 5, 6)};",
+ " a = 1, b = 2;",
+ " a = 1, b = 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f40060278cf7bbaca75632570dbadc10067591bb"
+ "shas": "30cf69eb0cc5543fe53be82f29cd0e0371e30cd1..a454c132f64a253a51cbf1a1455e74fca9343c23"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-replacement-test",
@@ -299,9 +335,19 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "f40060278cf7bbaca75632570dbadc10067591bb",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index 93ece10..297e28d 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-c = {d: (3, 4 + 5, 6)};",
+ "-a = 1, b = 2;",
+ " a = 1, b = 2;",
+ "+c = {d: (3, 4 + 5, 6)};"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "67e74b7145a061c1d8f576792167aab68c6be809"
+ "shas": "a454c132f64a253a51cbf1a1455e74fca9343c23..db24ea61ad00e73c91b0a4b616f333a5eac48f29"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-test",
@@ -345,9 +391,17 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "67e74b7145a061c1d8f576792167aab68c6be809",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index 297e28d..421bc7f 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1,2 +1 @@",
+ "-a = 1, b = 2;",
+ " c = {d: (3, 4 + 5, 6)};"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "12ce4e2077d01b8c8209ad272f1d0f715d9b0124"
+ "shas": "db24ea61ad00e73c91b0a4b616f333a5eac48f29..4ec8128c2ab11f7bf00c002d0fec6c8601b14c16"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-rest-test",
@@ -376,7 +430,14 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "12ce4e2077d01b8c8209ad272f1d0f715d9b0124",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index 421bc7f..e69de29 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1 +0,0 @@",
+ "-c = {d: (3, 4 + 5, 6)};"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "26df3b54cd036f1ed2bff8a0ca225ad680e23432"
+ "shas": "4ec8128c2ab11f7bf00c002d0fec6c8601b14c16..0ccf8092231ebc8ac92cc60fe614f1681bc03a89"
}]
diff --git a/test/corpus/diff-summaries/javascript/comment.json b/test/corpus/diff-summaries/javascript/comment.json
index 5cf094c5c..a1ba7d82b 100644
--- a/test/corpus/diff-summaries/javascript/comment.json
+++ b/test/corpus/diff-summaries/javascript/comment.json
@@ -7,9 +7,16 @@
"filePaths": [
"comment.js"
],
- "sha1": "51cb9277c2233716e2f002c08a23656f70425838",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index e69de29..a5821d2 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -0,0 +1 @@",
+ "+// This is a property"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "98ef3ccd95e55e93513f790185e4fc83ed93def2"
+ "shas": "81bc4513ad3979452e9e95586a5fbc9ca66eeadc..522a93132b55605393a0f7a5421f3d1f7b0d4a8c"
}
,{
"testCaseDescription": "javascript-comment-replacement-insert-test",
@@ -20,9 +27,20 @@
"filePaths": [
"comment.js"
],
- "sha1": "98ef3ccd95e55e93513f790185e4fc83ed93def2",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index a5821d2..761aa7a 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1 +1,5 @@",
+ "+/*",
+ "+ * This is a method",
+ "+*/",
+ "+// This is a property",
+ " // This is a property"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1ac3dd727429b94a67241d8941f5360892a30fae"
+ "shas": "522a93132b55605393a0f7a5421f3d1f7b0d4a8c..f0aa09e8712b14d61160b16073cac5fbd0276038"
}
,{
"testCaseDescription": "javascript-comment-delete-insert-test",
@@ -33,9 +51,21 @@
"filePaths": [
"comment.js"
],
- "sha1": "1ac3dd727429b94a67241d8941f5360892a30fae",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index 761aa7a..3b33406 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1,5 +1,3 @@",
+ "-/*",
+ "- * This is a method",
+ "-*/",
+ "+// This is a property",
+ " // This is a property",
+ " // This is a property"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "722ca07f3cc31c8d961494547fab727ec588e3d8"
+ "shas": "f0aa09e8712b14d61160b16073cac5fbd0276038..9402b254de81dabcddcbd6d7308911822b6f0f59"
}
,{
"testCaseDescription": "javascript-comment-replacement-test",
@@ -46,9 +76,21 @@
"filePaths": [
"comment.js"
],
- "sha1": "722ca07f3cc31c8d961494547fab727ec588e3d8",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index 3b33406..761aa7a 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1,3 +1,5 @@",
+ "-// This is a property",
+ "+/*",
+ "+ * This is a method",
+ "+*/",
+ " // This is a property",
+ " // This is a property"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ddbe0bb45770aad94db0b3db41bb85c6cf8667ea"
+ "shas": "9402b254de81dabcddcbd6d7308911822b6f0f59..ba788116c40403584cd03df9976350810a9b1162"
}
,{
"testCaseDescription": "javascript-comment-delete-replacement-test",
@@ -59,9 +101,21 @@
"filePaths": [
"comment.js"
],
- "sha1": "ddbe0bb45770aad94db0b3db41bb85c6cf8667ea",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index 761aa7a..c2a8148 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1,5 +1,4 @@",
+ "+// This is a property",
+ " /*",
+ " * This is a method",
+ " */",
+ "-// This is a property",
+ "-// This is a property"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "16f46467d4d4394f04d1098d53f86503eb75c645"
+ "shas": "ba788116c40403584cd03df9976350810a9b1162..05a2041be1630b8a7309163d4b863cd8966adbe0"
}
,{
"testCaseDescription": "javascript-comment-delete-test",
@@ -72,9 +126,19 @@
"filePaths": [
"comment.js"
],
- "sha1": "16f46467d4d4394f04d1098d53f86503eb75c645",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index c2a8148..7c74dcd 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1,4 +1,3 @@",
+ "-// This is a property",
+ " /*",
+ " * This is a method",
+ " */"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9be6ce33b023b9caecb8a2b0d01d7b040aa4da21"
+ "shas": "05a2041be1630b8a7309163d4b863cd8966adbe0..28ae9fb48ab99b60a709d3168a82f53017fa27a0"
}
,{
"testCaseDescription": "javascript-comment-delete-rest-test",
@@ -85,7 +149,16 @@
"filePaths": [
"comment.js"
],
- "sha1": "9be6ce33b023b9caecb8a2b0d01d7b040aa4da21",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index 7c74dcd..e69de29 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1,3 +0,0 @@",
+ "-/*",
+ "- * This is a method",
+ "-*/"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3061e328305d93ca2fd3a8aa7a86d645c4c28b15"
+ "shas": "28ae9fb48ab99b60a709d3168a82f53017fa27a0..8f7edd21ecef61769b82fb5a60a881f31ce30a01"
}]
diff --git a/test/corpus/diff-summaries/javascript/constructor-call.json b/test/corpus/diff-summaries/javascript/constructor-call.json
index 965a160aa..98781ff1c 100644
--- a/test/corpus/diff-summaries/javascript/constructor-call.json
+++ b/test/corpus/diff-summaries/javascript/constructor-call.json
@@ -25,9 +25,16 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "3bd8ebcbe86dd538120a517b6420d768e8ce2b4c",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index e69de29..9d723b9 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -0,0 +1 @@",
+ "+new module.Klass(1, \"two\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ce70ddd02a33da6279c6bf17d449df82c8832841"
+ "shas": "b1ed87edc6bf561edc524058ab781a95970a3258..692f777ed1db0b3284bd2728f6c651425e20ab34"
}
,{
"testCaseDescription": "javascript-constructor-call-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "ce70ddd02a33da6279c6bf17d449df82c8832841",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index 9d723b9..2c91b11 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1 +1,3 @@",
+ "+new module.Klass(1, \"three\");",
+ "+new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"two\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8487448225b5505389343c8393596e17ce1a54e8"
+ "shas": "692f777ed1db0b3284bd2728f6c651425e20ab34..e4d96364ed5caab5be836020193ea527a6cd6e55"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "8487448225b5505389343c8393596e17ce1a54e8",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index 2c91b11..892f542 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-new module.Klass(1, \"three\");",
+ "+new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"two\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0eba0fb788d00016c7515ce5c38c413191448474"
+ "shas": "e4d96364ed5caab5be836020193ea527a6cd6e55..c5f5c7389717f787423d9698a3e0593a965ffbd5"
}
,{
"testCaseDescription": "javascript-constructor-call-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "0eba0fb788d00016c7515ce5c38c413191448474",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index 892f542..2c91b11 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-new module.Klass(1, \"two\");",
+ "+new module.Klass(1, \"three\");",
+ " new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"two\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c1e0930ce2d9e9d05f967ee7857e1a8b7e80b9a2"
+ "shas": "c5f5c7389717f787423d9698a3e0593a965ffbd5..d17799b023d4e85c6e1d97220121da96a1323970"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "c1e0930ce2d9e9d05f967ee7857e1a8b7e80b9a2",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index 2c91b11..cd77b98 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1,3 +1,2 @@",
+ "-new module.Klass(1, \"three\");",
+ "-new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"two\");",
+ "+new module.Klass(1, \"three\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "723818ee1046fdbb4aed30a93ec6cc212062fdcd"
+ "shas": "d17799b023d4e85c6e1d97220121da96a1323970..ddc3d491ed287b5aee714bedf5c2de5ba46770ce"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "723818ee1046fdbb4aed30a93ec6cc212062fdcd",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index cd77b98..75f6a29 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1,2 +1 @@",
+ "-new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"three\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5899cfa5983c7be3dc0c389ca1d0288fb608e98b"
+ "shas": "ddc3d491ed287b5aee714bedf5c2de5ba46770ce..e0a37e9237220e1382c4502fdfbbb4cc10cf04e0"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "5899cfa5983c7be3dc0c389ca1d0288fb608e98b",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index 75f6a29..e69de29 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1 +0,0 @@",
+ "-new module.Klass(1, \"three\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "012105d0edaef241c26098d6e1680dab22bacbbc"
+ "shas": "e0a37e9237220e1382c4502fdfbbb4cc10cf04e0..41ab7cb7dc378bf229f7a08f1a03c0676483f435"
}]
diff --git a/test/corpus/diff-summaries/javascript/delete-operator.json b/test/corpus/diff-summaries/javascript/delete-operator.json
index 8c3419411..d134089b9 100644
--- a/test/corpus/diff-summaries/javascript/delete-operator.json
+++ b/test/corpus/diff-summaries/javascript/delete-operator.json
@@ -25,9 +25,16 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "979a03e21696fd6d2f5ef3c8c8e7473810cfc7c9",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index e69de29..c83346d 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -0,0 +1 @@",
+ "+delete thing['prop'];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b2de3290891a273baacbb28e1b384ac0f6e791ac"
+ "shas": "b5645de0a9c0002d8f44d302c200dd88ff113f52..d1aaae4cff971b6bd6647c77427eab5789728dea"
}
,{
"testCaseDescription": "javascript-delete-operator-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "b2de3290891a273baacbb28e1b384ac0f6e791ac",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index c83346d..7c8b990 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1 +1,3 @@",
+ "+delete thing.prop",
+ "+delete thing['prop'];",
+ " delete thing['prop'];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c15e1d0affd79055bf356a9576a0ccda17249a6f"
+ "shas": "d1aaae4cff971b6bd6647c77427eab5789728dea..6444b777c04540c4e0229617aaadcf274dbe092f"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "c15e1d0affd79055bf356a9576a0ccda17249a6f",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index 7c8b990..f506e36 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-delete thing.prop",
+ "+delete thing['prop'];",
+ " delete thing['prop'];",
+ " delete thing['prop'];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "947df4dfc78c0a7a15d61a245059d9cc66e52823"
+ "shas": "6444b777c04540c4e0229617aaadcf274dbe092f..ce69f237ff3cf767d8814435ffa957dadfeafa37"
}
,{
"testCaseDescription": "javascript-delete-operator-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "947df4dfc78c0a7a15d61a245059d9cc66e52823",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index f506e36..7c8b990 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-delete thing['prop'];",
+ "+delete thing.prop",
+ " delete thing['prop'];",
+ " delete thing['prop'];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f1f49151fc821413654af49d74417c7b200bbb46"
+ "shas": "ce69f237ff3cf767d8814435ffa957dadfeafa37..71f7d6db03225cbfcc31f2bbd6ab589e9183c55c"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "f1f49151fc821413654af49d74417c7b200bbb46",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index 7c8b990..2dfe079 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-delete thing.prop",
+ "-delete thing['prop'];",
+ " delete thing['prop'];",
+ "+delete thing.prop"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9f515bdf829eb8bc34256b20f43923933e001f30"
+ "shas": "71f7d6db03225cbfcc31f2bbd6ab589e9183c55c..629c83e185f6ed3c97976cc604dfb3c5f455c11b"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "9f515bdf829eb8bc34256b20f43923933e001f30",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index 2dfe079..9d68dfb 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1,2 +1 @@",
+ "-delete thing['prop'];",
+ " delete thing.prop"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9c59c645ed8417f8fd39ce4094a07c7fcdc009c3"
+ "shas": "629c83e185f6ed3c97976cc604dfb3c5f455c11b..cf1e4c5bef7af55d4866d7be93a24a523edbbf4f"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "9c59c645ed8417f8fd39ce4094a07c7fcdc009c3",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index 9d68dfb..e69de29 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1 +0,0 @@",
+ "-delete thing.prop"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "003fa853280eb9156b63626be54039b1bc67ea49"
+ "shas": "cf1e4c5bef7af55d4866d7be93a24a523edbbf4f..56f88d5286e94da2b11b7f6d0a35aa836d4f5921"
}]
diff --git a/test/corpus/diff-summaries/javascript/do-while-statement.json b/test/corpus/diff-summaries/javascript/do-while-statement.json
index 5b491cea4..49a1461c2 100644
--- a/test/corpus/diff-summaries/javascript/do-while-statement.json
+++ b/test/corpus/diff-summaries/javascript/do-while-statement.json
@@ -25,9 +25,16 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "ec8ba8297edb4d6d8dbc00d6f028116e0b58abe8",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index e69de29..d1ec804 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -0,0 +1 @@",
+ "+do { console.log(insert); } while (true);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "33549ab5882710be4c88bcfdf659400ce67f5c1d"
+ "shas": "cd322134775da8db98f5a151ec8e2f5d9eddd3cf..2b58702fac7ff187b0f41a31b6fae16718c0ec4c"
}
,{
"testCaseDescription": "javascript-do-while-statement-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "33549ab5882710be4c88bcfdf659400ce67f5c1d",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index d1ec804..d9a410d 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1 +1,3 @@",
+ "+do { console.log(replacement); } while (false);",
+ "+do { console.log(insert); } while (true);",
+ " do { console.log(insert); } while (true);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "969fbb30a28a983aaea07a0caf168258283b9e01"
+ "shas": "2b58702fac7ff187b0f41a31b6fae16718c0ec4c..fa2041b0ae98229dc1322fda8ebaa2d98dd4b1f7"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-insert-test",
@@ -141,9 +157,19 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "969fbb30a28a983aaea07a0caf168258283b9e01",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index d9a410d..4197835 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-do { console.log(replacement); } while (false);",
+ "+do { console.log(insert); } while (true);",
+ " do { console.log(insert); } while (true);",
+ " do { console.log(insert); } while (true);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b568ea7e0a262c3819571cb8b2b2286eb182583c"
+ "shas": "fa2041b0ae98229dc1322fda8ebaa2d98dd4b1f7..c7d0a76295cd609ed29a5c857ff2d885eefb3610"
}
,{
"testCaseDescription": "javascript-do-while-statement-replacement-test",
@@ -211,9 +237,19 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "b568ea7e0a262c3819571cb8b2b2286eb182583c",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index 4197835..d9a410d 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-do { console.log(insert); } while (true);",
+ "+do { console.log(replacement); } while (false);",
+ " do { console.log(insert); } while (true);",
+ " do { console.log(insert); } while (true);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4ae8d06981390b10da59e0f4c795f7d62606283e"
+ "shas": "c7d0a76295cd609ed29a5c857ff2d885eefb3610..8887ecec6e5dc8852e1f29ffe74c0b79c304e04e"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-replacement-test",
@@ -272,9 +308,19 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "4ae8d06981390b10da59e0f4c795f7d62606283e",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index d9a410d..c5291b4 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-do { console.log(replacement); } while (false);",
+ "-do { console.log(insert); } while (true);",
+ " do { console.log(insert); } while (true);",
+ "+do { console.log(replacement); } while (false);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f79ad68ff3a0efaed28e9aa75314d2f4705de647"
+ "shas": "8887ecec6e5dc8852e1f29ffe74c0b79c304e04e..888367feff9a28c449258cd99afd8ac90e069f76"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-test",
@@ -303,9 +349,17 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "f79ad68ff3a0efaed28e9aa75314d2f4705de647",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index c5291b4..6085cb1 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1,2 +1 @@",
+ "-do { console.log(insert); } while (true);",
+ " do { console.log(replacement); } while (false);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7472b66a363abaae79b52faab6dff2465746424d"
+ "shas": "888367feff9a28c449258cd99afd8ac90e069f76..622706434ac7e362f28c08d79f7d8302ec086757"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-rest-test",
@@ -334,7 +388,14 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "7472b66a363abaae79b52faab6dff2465746424d",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index 6085cb1..e69de29 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1 +0,0 @@",
+ "-do { console.log(replacement); } while (false);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1c17753ae9931d9d5b151bab4498c78c5b31c6c1"
+ "shas": "622706434ac7e362f28c08d79f7d8302ec086757..2795ba48a13af4b2c6f240761fd880dc6cd10c2b"
}]
diff --git a/test/corpus/diff-summaries/javascript/export.json b/test/corpus/diff-summaries/javascript/export.json
index bca1e3318..8072fd1fa 100644
--- a/test/corpus/diff-summaries/javascript/export.json
+++ b/test/corpus/diff-summaries/javascript/export.json
@@ -175,9 +175,26 @@
"filePaths": [
"export.js"
],
- "sha1": "7b67ddbc527cc15d1cbac33725dc0c4d79472c8c",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index e69de29..dcd9320 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -0,0 +1,11 @@",
+ "+export { name1, name2, name3, nameN };",
+ "+export { variable1 as name1, variable2 as name2, nameN };",
+ "+export let name1, name2, nameN;",
+ "+export let name1 = value1, name2 = value2, name3, nameN;",
+ "+export default namedFunction;",
+ "+export default function () { };",
+ "+export default function name1() { };",
+ "+export { name1 as default };",
+ "+export * from 'foo';",
+ "+export { name1, name2, nameN } from 'foo';",
+ "+export { import1 as name1, import2 as name2, nameN } from 'bar';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "cd9386b43e1ada367135a44899e2043964488f66"
+ "shas": "0eb14098d9cfc48fe7ffb44e37c71cb6cb58c878..5e2e89a442ac0f099046b72d57acaa03dc011ed9"
}
,{
"testCaseDescription": "javascript-export-replacement-insert-test",
@@ -521,9 +538,40 @@
"filePaths": [
"export.js"
],
- "sha1": "cd9386b43e1ada367135a44899e2043964488f66",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index dcd9320..c8b53ff 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,3 +1,25 @@",
+ "+export { name4, name5, name6, nameZ };",
+ "+export { variable2 as name2, variable3 as name3, nameY };",
+ "+export let name3, name4, nameT;",
+ "+export let name2 = value2, name3 = value3, name4, nameO;",
+ "+export default otherNamedFunction;",
+ "+export default function newName1() {};",
+ "+export default function () {};",
+ "+export { name2 as statement };",
+ "+export * from 'baz';",
+ "+export { name7, name8, nameP } from 'buzz';",
+ "+export { import6 as name6, import7 as name7, nameB } from 'fizz';",
+ "+export { name1, name2, name3, nameN };",
+ "+export { variable1 as name1, variable2 as name2, nameN };",
+ "+export let name1, name2, nameN;",
+ "+export let name1 = value1, name2 = value2, name3, nameN;",
+ "+export default namedFunction;",
+ "+export default function () { };",
+ "+export default function name1() { };",
+ "+export { name1 as default };",
+ "+export * from 'foo';",
+ "+export { name1, name2, nameN } from 'foo';",
+ "+export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ " export { name1, name2, name3, nameN };",
+ " export { variable1 as name1, variable2 as name2, nameN };",
+ " export let name1, name2, nameN;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5960bd1b757244b4df82cae4bceabe2055ac9c04"
+ "shas": "5e2e89a442ac0f099046b72d57acaa03dc011ed9..9e81bf04d8f7a930fb0a612fc5230af600c7c5d2"
}
,{
"testCaseDescription": "javascript-export-delete-insert-test",
@@ -1254,9 +1302,40 @@
"filePaths": [
"export.js"
],
- "sha1": "5960bd1b757244b4df82cae4bceabe2055ac9c04",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index c8b53ff..ad3f21a 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,14 +1,14 @@",
+ "-export { name4, name5, name6, nameZ };",
+ "-export { variable2 as name2, variable3 as name3, nameY };",
+ "-export let name3, name4, nameT;",
+ "-export let name2 = value2, name3 = value3, name4, nameO;",
+ "-export default otherNamedFunction;",
+ "-export default function newName1() {};",
+ "-export default function () {};",
+ "-export { name2 as statement };",
+ "-export * from 'baz';",
+ "-export { name7, name8, nameP } from 'buzz';",
+ "-export { import6 as name6, import7 as name7, nameB } from 'fizz';",
+ "+export { name1, name2, name3, nameN };",
+ "+export { variable1 as name1, variable2 as name2, nameN };",
+ "+export let name1, name2, nameN;",
+ "+export let name1 = value1, name2 = value2, name3, nameN;",
+ "+export default namedFunction;",
+ "+export default function () { };",
+ "+export default function name1() { };",
+ "+export { name1 as default };",
+ "+export * from 'foo';",
+ "+export { name1, name2, nameN } from 'foo';",
+ "+export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ " export { name1, name2, name3, nameN };",
+ " export { variable1 as name1, variable2 as name2, nameN };",
+ " export let name1, name2, nameN;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3e09142eeccf41374af934cc1a492e1660a202be"
+ "shas": "9e81bf04d8f7a930fb0a612fc5230af600c7c5d2..d1bc421a42e531d555179f1135e64e9f19d57095"
}
,{
"testCaseDescription": "javascript-export-replacement-test",
@@ -1678,9 +1757,40 @@
"filePaths": [
"export.js"
],
- "sha1": "3e09142eeccf41374af934cc1a492e1660a202be",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index ad3f21a..c8b53ff 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,14 +1,14 @@",
+ "-export { name1, name2, name3, nameN };",
+ "-export { variable1 as name1, variable2 as name2, nameN };",
+ "-export let name1, name2, nameN;",
+ "-export let name1 = value1, name2 = value2, name3, nameN;",
+ "-export default namedFunction;",
+ "-export default function () { };",
+ "-export default function name1() { };",
+ "-export { name1 as default };",
+ "-export * from 'foo';",
+ "-export { name1, name2, nameN } from 'foo';",
+ "-export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ "+export { name4, name5, name6, nameZ };",
+ "+export { variable2 as name2, variable3 as name3, nameY };",
+ "+export let name3, name4, nameT;",
+ "+export let name2 = value2, name3 = value3, name4, nameO;",
+ "+export default otherNamedFunction;",
+ "+export default function newName1() {};",
+ "+export default function () {};",
+ "+export { name2 as statement };",
+ "+export * from 'baz';",
+ "+export { name7, name8, nameP } from 'buzz';",
+ "+export { import6 as name6, import7 as name7, nameB } from 'fizz';",
+ " export { name1, name2, name3, nameN };",
+ " export { variable1 as name1, variable2 as name2, nameN };",
+ " export let name1, name2, nameN;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b1d4ad7f530f1b762b1a4fc4f4d7597666b3f4ec"
+ "shas": "d1bc421a42e531d555179f1135e64e9f19d57095..61d845cfdc6aaaba0c4fa01fb8ca41f79556ac37"
}
,{
"testCaseDescription": "javascript-export-delete-replacement-test",
@@ -2189,9 +2299,55 @@
"filePaths": [
"export.js"
],
- "sha1": "b1d4ad7f530f1b762b1a4fc4f4d7597666b3f4ec",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index c8b53ff..281c672 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,25 +1,3 @@",
+ "-export { name4, name5, name6, nameZ };",
+ "-export { variable2 as name2, variable3 as name3, nameY };",
+ "-export let name3, name4, nameT;",
+ "-export let name2 = value2, name3 = value3, name4, nameO;",
+ "-export default otherNamedFunction;",
+ "-export default function newName1() {};",
+ "-export default function () {};",
+ "-export { name2 as statement };",
+ "-export * from 'baz';",
+ "-export { name7, name8, nameP } from 'buzz';",
+ "-export { import6 as name6, import7 as name7, nameB } from 'fizz';",
+ "-export { name1, name2, name3, nameN };",
+ "-export { variable1 as name1, variable2 as name2, nameN };",
+ "-export let name1, name2, nameN;",
+ "-export let name1 = value1, name2 = value2, name3, nameN;",
+ "-export default namedFunction;",
+ "-export default function () { };",
+ "-export default function name1() { };",
+ "-export { name1 as default };",
+ "-export * from 'foo';",
+ "-export { name1, name2, nameN } from 'foo';",
+ "-export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ " export { name1, name2, name3, nameN };",
+ " export { variable1 as name1, variable2 as name2, nameN };",
+ " export let name1, name2, nameN;",
+ "@@ -31,3 +9,14 @@ export { name1 as default };",
+ " export * from 'foo';",
+ " export { name1, name2, nameN } from 'foo';",
+ " export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ "+export { name4, name5, name6, nameZ };",
+ "+export { variable2 as name2, variable3 as name3, nameY };",
+ "+export let name3, name4, nameT;",
+ "+export let name2 = value2, name3 = value3, name4, nameO;",
+ "+export default otherNamedFunction;",
+ "+export default function newName1() {};",
+ "+export default function () {};",
+ "+export { name2 as statement };",
+ "+export * from 'baz';",
+ "+export { name7, name8, nameP } from 'buzz';",
+ "+export { import6 as name6, import7 as name7, nameB } from 'fizz';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ef3fc45439ff4e4a2a491636770addcee77c5796"
+ "shas": "61d845cfdc6aaaba0c4fa01fb8ca41f79556ac37..06bbce70f8962416f84a41ea00019bfb28b73bf9"
}
,{
"testCaseDescription": "javascript-export-delete-test",
@@ -2370,9 +2526,29 @@
"filePaths": [
"export.js"
],
- "sha1": "ef3fc45439ff4e4a2a491636770addcee77c5796",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index 281c672..e105ba7 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,14 +1,3 @@",
+ "-export { name1, name2, name3, nameN };",
+ "-export { variable1 as name1, variable2 as name2, nameN };",
+ "-export let name1, name2, nameN;",
+ "-export let name1 = value1, name2 = value2, name3, nameN;",
+ "-export default namedFunction;",
+ "-export default function () { };",
+ "-export default function name1() { };",
+ "-export { name1 as default };",
+ "-export * from 'foo';",
+ "-export { name1, name2, nameN } from 'foo';",
+ "-export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ " export { name4, name5, name6, nameZ };",
+ " export { variable2 as name2, variable3 as name3, nameY };",
+ " export let name3, name4, nameT;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b108c428f25f1605b690e84daa6f1c8afbcb8466"
+ "shas": "06bbce70f8962416f84a41ea00019bfb28b73bf9..d1daa5ccf312ddb7b243f8adf15955fac3df1d63"
}
,{
"testCaseDescription": "javascript-export-delete-rest-test",
@@ -2551,7 +2727,24 @@
"filePaths": [
"export.js"
],
- "sha1": "b108c428f25f1605b690e84daa6f1c8afbcb8466",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index e105ba7..e69de29 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,11 +0,0 @@",
+ "-export { name4, name5, name6, nameZ };",
+ "-export { variable2 as name2, variable3 as name3, nameY };",
+ "-export let name3, name4, nameT;",
+ "-export let name2 = value2, name3 = value3, name4, nameO;",
+ "-export default otherNamedFunction;",
+ "-export default function newName1() {};",
+ "-export default function () {};",
+ "-export { name2 as statement };",
+ "-export * from 'baz';",
+ "-export { name7, name8, nameP } from 'buzz';",
+ "-export { import6 as name6, import7 as name7, nameB } from 'fizz';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ddc540ac245ab0b5fd645525c53e4326f07dd253"
+ "shas": "d1daa5ccf312ddb7b243f8adf15955fac3df1d63..925b73e9fde76236d0b037d687edcc925a5cef9a"
}]
diff --git a/test/corpus/diff-summaries/javascript/false.json b/test/corpus/diff-summaries/javascript/false.json
index 135a36092..f64b400e6 100644
--- a/test/corpus/diff-summaries/javascript/false.json
+++ b/test/corpus/diff-summaries/javascript/false.json
@@ -25,9 +25,16 @@
"filePaths": [
"false.js"
],
- "sha1": "04aded71e587d0bada2c50fd567023d9de7f477c",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index e69de29..8a63946 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -0,0 +1 @@",
+ "+false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "74941c080527d8accd5c74955fd31110e7be5509"
+ "shas": "a56c14e19dec2910d36460e4fca6496da46f6240..6b1a30d6be2d43907c3a1faf581db6c9fe6cc88a"
}
,{
"testCaseDescription": "javascript-false-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"false.js"
],
- "sha1": "74941c080527d8accd5c74955fd31110e7be5509",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 8a63946..86574b1 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1 +1,3 @@",
+ "+return false;",
+ "+false;",
+ " false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ef20d47afcee8970df0617a652b700e2ea002d85"
+ "shas": "6b1a30d6be2d43907c3a1faf581db6c9fe6cc88a..122e0fae24e99d4f534bb461d9d5fa2900c70e55"
}
,{
"testCaseDescription": "javascript-false-delete-insert-test",
@@ -117,9 +133,19 @@
"filePaths": [
"false.js"
],
- "sha1": "ef20d47afcee8970df0617a652b700e2ea002d85",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 86574b1..7bae7c5 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1,3 +1,3 @@",
+ "-return false;",
+ "+false;",
+ " false;",
+ " false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c5ca8f1fedc05537db6d2a923dc63933396e1bc3"
+ "shas": "122e0fae24e99d4f534bb461d9d5fa2900c70e55..6d5ec0ada3f32284c9922934304c708333da7e1f"
}
,{
"testCaseDescription": "javascript-false-replacement-test",
@@ -163,9 +189,19 @@
"filePaths": [
"false.js"
],
- "sha1": "c5ca8f1fedc05537db6d2a923dc63933396e1bc3",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 7bae7c5..86574b1 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1,3 +1,3 @@",
+ "-false;",
+ "+return false;",
+ " false;",
+ " false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "38316340683de061a83087c8aa02ae1abbb37479"
+ "shas": "6d5ec0ada3f32284c9922934304c708333da7e1f..7291f772ca242bae0a92ab87c1ab6ec2be28d4c1"
}
,{
"testCaseDescription": "javascript-false-delete-replacement-test",
@@ -224,9 +260,19 @@
"filePaths": [
"false.js"
],
- "sha1": "38316340683de061a83087c8aa02ae1abbb37479",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 86574b1..85b5be9 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1,3 +1,2 @@",
+ "-return false;",
+ "-false;",
+ " false;",
+ "+return false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3e4d9841d8064e0e35fb4b0fb5a6240ac7f538e6"
+ "shas": "7291f772ca242bae0a92ab87c1ab6ec2be28d4c1..018e3b49010dd5359d8071f4a856b6ccef409645"
}
,{
"testCaseDescription": "javascript-false-delete-test",
@@ -255,9 +301,17 @@
"filePaths": [
"false.js"
],
- "sha1": "3e4d9841d8064e0e35fb4b0fb5a6240ac7f538e6",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 85b5be9..1f328b3 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1,2 +1 @@",
+ "-false;",
+ " return false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7bee29b9f6ea9ffdaf9141f171828b9e5a3b4e47"
+ "shas": "018e3b49010dd5359d8071f4a856b6ccef409645..bda912eec94150ac764d032b1243ec8dba01f3f0"
}
,{
"testCaseDescription": "javascript-false-delete-rest-test",
@@ -286,7 +340,14 @@
"filePaths": [
"false.js"
],
- "sha1": "7bee29b9f6ea9ffdaf9141f171828b9e5a3b4e47",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 1f328b3..e69de29 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1 +0,0 @@",
+ "-return false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "559546b09a86fffc79e8283d8f7567d491c07e90"
+ "shas": "bda912eec94150ac764d032b1243ec8dba01f3f0..f6dfeb42af9db740677fd60341ea39da711f7c81"
}]
diff --git a/test/corpus/diff-summaries/javascript/for-in-statement.json b/test/corpus/diff-summaries/javascript/for-in-statement.json
index 1f3ca0578..2151f2b56 100644
--- a/test/corpus/diff-summaries/javascript/for-in-statement.json
+++ b/test/corpus/diff-summaries/javascript/for-in-statement.json
@@ -25,9 +25,16 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "59c52a0ddb5e652e5b5108d0724541989a6d83aa",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index e69de29..f928287 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -0,0 +1 @@",
+ "+for (thing in things) { thing(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "29b666fa2472eecf7b9d073a0293fc0d86cbee77"
+ "shas": "75f87f22428c68545ebb3f876a1b09caf59d75c9..1d91306ffc69509679ae514ecc2a3403dc94aefb"
}
,{
"testCaseDescription": "javascript-for-in-statement-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "29b666fa2472eecf7b9d073a0293fc0d86cbee77",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index f928287..4a482e9 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1 +1,3 @@",
+ "+for (item in items) { item(); }",
+ "+for (thing in things) { thing(); }",
+ " for (thing in things) { thing(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b7391d72e98da90810b11a4ac0ed9027c4ddec08"
+ "shas": "1d91306ffc69509679ae514ecc2a3403dc94aefb..2f951d1d02db4475f786a87f7077648822ef26d3"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-insert-test",
@@ -168,9 +184,19 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "b7391d72e98da90810b11a4ac0ed9027c4ddec08",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index 4a482e9..e949baf 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (item in items) { item(); }",
+ "+for (thing in things) { thing(); }",
+ " for (thing in things) { thing(); }",
+ " for (thing in things) { thing(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "02ace41153aabc248b4f4c3bbe70edd6cf930933"
+ "shas": "2f951d1d02db4475f786a87f7077648822ef26d3..31f13f455d1c9d9efae42c7695abae57acf4684a"
}
,{
"testCaseDescription": "javascript-for-in-statement-replacement-test",
@@ -265,9 +291,19 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "02ace41153aabc248b4f4c3bbe70edd6cf930933",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index e949baf..4a482e9 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (thing in things) { thing(); }",
+ "+for (item in items) { item(); }",
+ " for (thing in things) { thing(); }",
+ " for (thing in things) { thing(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "843d56f80f3f9e2e7f2940b4f9382415fb00907c"
+ "shas": "31f13f455d1c9d9efae42c7695abae57acf4684a..20bf2c4356e71329f5e131bec7be78669308acc8"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-replacement-test",
@@ -326,9 +362,19 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "843d56f80f3f9e2e7f2940b4f9382415fb00907c",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index 4a482e9..6b5f12a 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-for (item in items) { item(); }",
+ "-for (thing in things) { thing(); }",
+ " for (thing in things) { thing(); }",
+ "+for (item in items) { item(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0d0d6478c7e57258561455f0ce7b3d3f416f5ae5"
+ "shas": "20bf2c4356e71329f5e131bec7be78669308acc8..cc6e8abe393b4d3c5e2b919a60c832b78ad0a4cd"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-test",
@@ -357,9 +403,17 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "0d0d6478c7e57258561455f0ce7b3d3f416f5ae5",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index 6b5f12a..a3d8882 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1,2 +1 @@",
+ "-for (thing in things) { thing(); }",
+ " for (item in items) { item(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "90c8a228bd3e7b8106f7a6461b376abc0055ec37"
+ "shas": "cc6e8abe393b4d3c5e2b919a60c832b78ad0a4cd..71a7b11ea45ba6cae99bbc5d1bdad0c7eb526a3b"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-rest-test",
@@ -388,7 +442,14 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "90c8a228bd3e7b8106f7a6461b376abc0055ec37",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index a3d8882..e69de29 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1 +0,0 @@",
+ "-for (item in items) { item(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d2246a50ed33ef4c748bfdaf80bbf4eb41cc6c57"
+ "shas": "71a7b11ea45ba6cae99bbc5d1bdad0c7eb526a3b..d1b2bee18a7da4fefa2a4786b2f692fc5795f48c"
}]
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 216709fff..bca171c0b 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
@@ -25,9 +25,16 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "d42f86b317b470d5207108107a9710b5a66b7693",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index e69de29..c467478 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -0,0 +1 @@",
+ "+for (key in something && i = 0; i < n; i++) { doSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "71e0fa7e41a874b0a5d718c95f074ace55cc9232"
+ "shas": "1c2dbb18fb6fc930b3d0e6bb31a559a853be5c63..974a2623d96129b8a5eb74659c0040931fe6597a"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "71e0fa7e41a874b0a5d718c95f074ace55cc9232",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index c467478..0147d31 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1 +1,3 @@",
+ "+for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
+ "+for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6bac9b37cf2cf093c337582d9de14afa128fed17"
+ "shas": "974a2623d96129b8a5eb74659c0040931fe6597a..37f9b64351b20f87cdd2d65e794e8b43ea684959"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test",
@@ -141,9 +157,19 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "6bac9b37cf2cf093c337582d9de14afa128fed17",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index 0147d31..306fa88 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
+ "+for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "149bca27f95242b5072ce36f019f298a300f97d3"
+ "shas": "37f9b64351b20f87cdd2d65e794e8b43ea684959..639c4e9d99aa30a48f0403a42eaf81f85a194e22"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test",
@@ -211,9 +237,19 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "149bca27f95242b5072ce36f019f298a300f97d3",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index 306fa88..0147d31 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ "+for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0a7c075c24681bfa818dffe5a91a41c59d533fcc"
+ "shas": "639c4e9d99aa30a48f0403a42eaf81f85a194e22..8d475ef797fcd08a47c73f033c305642c4279115"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test",
@@ -272,9 +308,19 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "0a7c075c24681bfa818dffe5a91a41c59d533fcc",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index 0147d31..f23fa31 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
+ "-for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ "+for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9ecf6acc87328e9ca74836a467411d20838ceeae"
+ "shas": "8d475ef797fcd08a47c73f033c305642c4279115..d2051aee8f163a567cf3a5ff4060579795e0a2a1"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-test",
@@ -303,9 +349,17 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "9ecf6acc87328e9ca74836a467411d20838ceeae",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index f23fa31..e968160 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1,2 +1 @@",
+ "-for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e1f719858553a9e12274fec57ae67a38a67719b3"
+ "shas": "d2051aee8f163a567cf3a5ff4060579795e0a2a1..068a5eccf07c8be3b3a95d6eceadf7062d7b942d"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test",
@@ -334,7 +388,14 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "e1f719858553a9e12274fec57ae67a38a67719b3",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index e968160..e69de29 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1 +0,0 @@",
+ "-for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f9d31193b2e0de3664fd90baf4bf0f036eed7805"
+ "shas": "068a5eccf07c8be3b3a95d6eceadf7062d7b942d..9c2fa1f20200ecb26074ec348c75c13c22138f87"
}]
diff --git a/test/corpus/diff-summaries/javascript/for-of-statement.json b/test/corpus/diff-summaries/javascript/for-of-statement.json
index 15bc97e81..aca0dea49 100644
--- a/test/corpus/diff-summaries/javascript/for-of-statement.json
+++ b/test/corpus/diff-summaries/javascript/for-of-statement.json
@@ -25,9 +25,16 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "f9d31193b2e0de3664fd90baf4bf0f036eed7805",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index e69de29..1ed2754 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -0,0 +1 @@",
+ "+for (let item of items) { process(item); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fdb12c1fe737ef373806b4986172a03007e238c1"
+ "shas": "9c2fa1f20200ecb26074ec348c75c13c22138f87..c46e44d842f77789f61d1f25221f0449f2d580c5"
}
,{
"testCaseDescription": "javascript-for-of-statement-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "fdb12c1fe737ef373806b4986172a03007e238c1",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index 1ed2754..ab20ded 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1 +1,3 @@",
+ "+for (let thing of things) { process(thing); };",
+ "+for (let item of items) { process(item); };",
+ " for (let item of items) { process(item); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "940950f103116ec45a222f21de8cdbcc49f48795"
+ "shas": "c46e44d842f77789f61d1f25221f0449f2d580c5..1c06836a9dafef9518b54b9409dc10e9e4402666"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-insert-test",
@@ -168,9 +184,19 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "940950f103116ec45a222f21de8cdbcc49f48795",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index ab20ded..19561a3 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (let thing of things) { process(thing); };",
+ "+for (let item of items) { process(item); };",
+ " for (let item of items) { process(item); };",
+ " for (let item of items) { process(item); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "682b758ed60acc11b5c83d746f3822ef9e4f870c"
+ "shas": "1c06836a9dafef9518b54b9409dc10e9e4402666..4c79ce75c12d7e2b77bd33d6f7e4f1d839ee88a8"
}
,{
"testCaseDescription": "javascript-for-of-statement-replacement-test",
@@ -265,9 +291,19 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "682b758ed60acc11b5c83d746f3822ef9e4f870c",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index 19561a3..ab20ded 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (let item of items) { process(item); };",
+ "+for (let thing of things) { process(thing); };",
+ " for (let item of items) { process(item); };",
+ " for (let item of items) { process(item); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "661909ac91a22c549b5ba5e40a492192452e9126"
+ "shas": "4c79ce75c12d7e2b77bd33d6f7e4f1d839ee88a8..cd97645bfe60051a1bbd7a490394b00b6df48a7d"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-replacement-test",
@@ -326,9 +362,19 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "661909ac91a22c549b5ba5e40a492192452e9126",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index ab20ded..62db34f 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-for (let thing of things) { process(thing); };",
+ "-for (let item of items) { process(item); };",
+ " for (let item of items) { process(item); };",
+ "+for (let thing of things) { process(thing); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9e29ecdff2b47416f53acc8e1acd4d51415dedf8"
+ "shas": "cd97645bfe60051a1bbd7a490394b00b6df48a7d..3fd962ae8d2bc510b50e7e85ef1ce4ad04375eb8"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-test",
@@ -357,9 +403,17 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "9e29ecdff2b47416f53acc8e1acd4d51415dedf8",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index 62db34f..5170ce4 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1,2 +1 @@",
+ "-for (let item of items) { process(item); };",
+ " for (let thing of things) { process(thing); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "bbd14a09e7756c7f89efaaa9bfde692fcd16a0e2"
+ "shas": "3fd962ae8d2bc510b50e7e85ef1ce4ad04375eb8..821a3c7b8a7b00f8a8ad7967aed163a12f042d10"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-rest-test",
@@ -388,7 +442,14 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "bbd14a09e7756c7f89efaaa9bfde692fcd16a0e2",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index 5170ce4..e69de29 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1 +0,0 @@",
+ "-for (let thing of things) { process(thing); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a155a2bd652ca5aaa95ea8e31c7eac9662aa07f9"
+ "shas": "821a3c7b8a7b00f8a8ad7967aed163a12f042d10..0b1a50d075cdb5202c523f929502c24a9fce63ce"
}]
diff --git a/test/corpus/diff-summaries/javascript/for-statement.json b/test/corpus/diff-summaries/javascript/for-statement.json
index e3599780e..b5610becd 100644
--- a/test/corpus/diff-summaries/javascript/for-statement.json
+++ b/test/corpus/diff-summaries/javascript/for-statement.json
@@ -25,9 +25,16 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "3b37b1f1ec583cf921f87b304b606d12b388bcd5",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index e69de29..2f51258 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -0,0 +1 @@",
+ "+for (i = 0, init(); i < 10; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b871597febfb405a61f6fe7b2bc357fb03aeafe3"
+ "shas": "eaeb10729b105d290f4091fea5f04c34030bb5a5..40bfcf71debc3d20926578f5d788f319165ccdbb"
}
,{
"testCaseDescription": "javascript-for-statement-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "b871597febfb405a61f6fe7b2bc357fb03aeafe3",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index 2f51258..095241f 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1 +1,3 @@",
+ "+for (i = 0, init(); i < 100; i++) { log(i); }",
+ "+for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9b1d937b78222de41c3c5144f67f075bb43e2c13"
+ "shas": "40bfcf71debc3d20926578f5d788f319165ccdbb..14acd05cf2f47feba3234c70af8afe86828370ce"
}
,{
"testCaseDescription": "javascript-for-statement-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "9b1d937b78222de41c3c5144f67f075bb43e2c13",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index 095241f..9b0e26d 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (i = 0, init(); i < 100; i++) { log(i); }",
+ "+for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c650295f1ecd192eaeae937b7f6175202839a1ea"
+ "shas": "14acd05cf2f47feba3234c70af8afe86828370ce..26784319f5f567d3017095b6f9d0ca081043b817"
}
,{
"testCaseDescription": "javascript-for-statement-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "c650295f1ecd192eaeae937b7f6175202839a1ea",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index 9b0e26d..095241f 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (i = 0, init(); i < 10; i++) { log(i); }",
+ "+for (i = 0, init(); i < 100; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "92349c8f6582da8eee5c83e7e9d6a7e159b6bd79"
+ "shas": "26784319f5f567d3017095b6f9d0ca081043b817..5b15f8e9f8b68a8e4f4ba6ec6642a3cb37db7c60"
}
,{
"testCaseDescription": "javascript-for-statement-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "92349c8f6582da8eee5c83e7e9d6a7e159b6bd79",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index 095241f..39af699 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-for (i = 0, init(); i < 100; i++) { log(i); }",
+ "-for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }",
+ "+for (i = 0, init(); i < 100; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ba90f5edb467195216326c4f5da878084a2247c8"
+ "shas": "5b15f8e9f8b68a8e4f4ba6ec6642a3cb37db7c60..70806220f9fba3804c162aed68cdfcb25c39ff0a"
}
,{
"testCaseDescription": "javascript-for-statement-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "ba90f5edb467195216326c4f5da878084a2247c8",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index 39af699..de8ae87 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1,2 +1 @@",
+ "-for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 100; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c20c08f9fc64911ac52a4f87ca4a60c7fb4c76b5"
+ "shas": "70806220f9fba3804c162aed68cdfcb25c39ff0a..9d01a0008d001fc966736db7d1583e0415da98fd"
}
,{
"testCaseDescription": "javascript-for-statement-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "c20c08f9fc64911ac52a4f87ca4a60c7fb4c76b5",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index de8ae87..e69de29 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1 +0,0 @@",
+ "-for (i = 0, init(); i < 100; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f5dfc0945ffae36e0f9784dcfeb8472344055afc"
+ "shas": "9d01a0008d001fc966736db7d1583e0415da98fd..10c888c0caabf36cb211a96640afbe435dfad3fb"
}]
diff --git a/test/corpus/diff-summaries/javascript/function-call-args.json b/test/corpus/diff-summaries/javascript/function-call-args.json
index 4ab293f4d..b73044ee5 100644
--- a/test/corpus/diff-summaries/javascript/function-call-args.json
+++ b/test/corpus/diff-summaries/javascript/function-call-args.json
@@ -25,9 +25,16 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "6087206d2569a100e711f522134188e6f4477aec",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index e69de29..699333d 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -0,0 +1 @@",
+ "+someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2a33781a84e417f58c35f1842a5756a306d96e16"
+ "shas": "5d5d40b2fa515dfcb7494d9b83f22687c56de0f5..d2a8bcf4eb5c5193cb358f09a81b0239be2a84ad"
}
,{
"testCaseDescription": "javascript-function-call-args-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "2a33781a84e417f58c35f1842a5756a306d96e16",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index 699333d..3f4ee6e 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1 +1,3 @@",
+ "+someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)",
+ "+someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "00cbc206ce3e849a4f008481a388fe2cd16cdab0"
+ "shas": "d2a8bcf4eb5c5193cb358f09a81b0239be2a84ad..539cee544c8600977bd76181a692ef4e27c4b759"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-insert-test",
@@ -249,9 +265,19 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "00cbc206ce3e849a4f008481a388fe2cd16cdab0",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index 3f4ee6e..dc419cb 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1,3 +1,3 @@",
+ "-someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)",
+ "+someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fe0562a6af2ef816cd033495c6dab8a098e9abd1"
+ "shas": "539cee544c8600977bd76181a692ef4e27c4b759..f808e14f78dbe08885649be38dff25564f90fd98"
}
,{
"testCaseDescription": "javascript-function-call-args-replacement-test",
@@ -427,9 +453,19 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "fe0562a6af2ef816cd033495c6dab8a098e9abd1",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index dc419cb..3f4ee6e 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1,3 +1,3 @@",
+ "-someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ "+someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3ffd66b0af62a4993f1ec9cec204e476a4b8f571"
+ "shas": "f808e14f78dbe08885649be38dff25564f90fd98..6df8cc03d89ad9408f10b3e84a8168891e16c824"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-replacement-test",
@@ -488,9 +524,19 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "3ffd66b0af62a4993f1ec9cec204e476a4b8f571",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index 3f4ee6e..cae967b 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1,3 +1,2 @@",
+ "-someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)",
+ "-someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ "+someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ee3a4e126eb1e8e72d6066c91087fb820fe81f81"
+ "shas": "6df8cc03d89ad9408f10b3e84a8168891e16c824..8fe5a2260c0258b29e266f904dcdb1dbe02d4c10"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-test",
@@ -519,9 +565,17 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "ee3a4e126eb1e8e72d6066c91087fb820fe81f81",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index cae967b..0d19573 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1,2 +1 @@",
+ "-someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f68da3ce3086b28dbf986f818ff4e85b20f72a1c"
+ "shas": "8fe5a2260c0258b29e266f904dcdb1dbe02d4c10..657ddea03b3413ea6f2d4e8546403ec115769828"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-rest-test",
@@ -550,7 +604,14 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "f68da3ce3086b28dbf986f818ff4e85b20f72a1c",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index 0d19573..e69de29 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1 +0,0 @@",
+ "-someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3bd8ebcbe86dd538120a517b6420d768e8ce2b4c"
+ "shas": "657ddea03b3413ea6f2d4e8546403ec115769828..b1ed87edc6bf561edc524058ab781a95970a3258"
}]
diff --git a/test/corpus/diff-summaries/javascript/function-call.json b/test/corpus/diff-summaries/javascript/function-call.json
index bfad6ac6f..f61405e32 100644
--- a/test/corpus/diff-summaries/javascript/function-call.json
+++ b/test/corpus/diff-summaries/javascript/function-call.json
@@ -25,9 +25,16 @@
"filePaths": [
"function-call.js"
],
- "sha1": "1a9472e94c365639f5f2b5c519a06c2daf17c630",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index e69de29..8bd95e0 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -0,0 +1 @@",
+ "+someFunction(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "aea81a7aab8e43746db84c917498d022cad8f88b"
+ "shas": "5ef42771e35b5af39f3befe137fedf40f174a5c7..00b36bff0934786a0071eff76e45c17c464e432a"
}
,{
"testCaseDescription": "javascript-function-call-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"function-call.js"
],
- "sha1": "aea81a7aab8e43746db84c917498d022cad8f88b",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index 8bd95e0..6bb4cf3 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1 +1,3 @@",
+ "+someFunction(arg1, \"arg3\");",
+ "+someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a665ddd2de9f0b3f6cb01dac3885746472685a02"
+ "shas": "00b36bff0934786a0071eff76e45c17c464e432a..520cba16d2faea8fd35a81086ea0a0b2405bf082"
}
,{
"testCaseDescription": "javascript-function-call-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"function-call.js"
],
- "sha1": "a665ddd2de9f0b3f6cb01dac3885746472685a02",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index 6bb4cf3..b38c232 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-someFunction(arg1, \"arg3\");",
+ "+someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3c91447c23d8af65a9d5b3fdad3d2223dc9c9b8c"
+ "shas": "520cba16d2faea8fd35a81086ea0a0b2405bf082..8f84b861874020df6e144f16bbccb5221b1543e4"
}
,{
"testCaseDescription": "javascript-function-call-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"function-call.js"
],
- "sha1": "3c91447c23d8af65a9d5b3fdad3d2223dc9c9b8c",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index b38c232..6bb4cf3 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-someFunction(arg1, \"arg2\");",
+ "+someFunction(arg1, \"arg3\");",
+ " someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "92454603aeea12b9db63daaf4ff448a3ad866fc6"
+ "shas": "8f84b861874020df6e144f16bbccb5221b1543e4..718e8939aaef9685a140e371b050e8933450a215"
}
,{
"testCaseDescription": "javascript-function-call-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"function-call.js"
],
- "sha1": "92454603aeea12b9db63daaf4ff448a3ad866fc6",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index 6bb4cf3..3e15c6a 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1,3 +1,2 @@",
+ "-someFunction(arg1, \"arg3\");",
+ "-someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg2\");",
+ "+someFunction(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b5ba13c145b484c83750280711b5a8dbf9339b2a"
+ "shas": "718e8939aaef9685a140e371b050e8933450a215..35112398ed93567a624e79597194400f3a6ba5ed"
}
,{
"testCaseDescription": "javascript-function-call-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"function-call.js"
],
- "sha1": "b5ba13c145b484c83750280711b5a8dbf9339b2a",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index 3e15c6a..1add64b 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1,2 +1 @@",
+ "-someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "200d34900ee17186bda5fbf861a3960c8e0053e4"
+ "shas": "35112398ed93567a624e79597194400f3a6ba5ed..2928901cff45e08e275b3c7cc5559704326f2974"
}
,{
"testCaseDescription": "javascript-function-call-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"function-call.js"
],
- "sha1": "200d34900ee17186bda5fbf861a3960c8e0053e4",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index 1add64b..e69de29 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1 +0,0 @@",
+ "-someFunction(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3a19dee8da1e0544c2cf975d850a6ce707912b35"
+ "shas": "2928901cff45e08e275b3c7cc5559704326f2974..f8662860eb083b9e95b5cc1c706a7872a4779532"
}]
diff --git a/test/corpus/diff-summaries/javascript/function.json b/test/corpus/diff-summaries/javascript/function.json
index 3afc4e77d..f3e71eab3 100644
--- a/test/corpus/diff-summaries/javascript/function.json
+++ b/test/corpus/diff-summaries/javascript/function.json
@@ -25,9 +25,16 @@
"filePaths": [
"function.js"
],
- "sha1": "e1f7c5a495d4e15d24ac325f6dec565f21f021e8",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index e69de29..2d8d739 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -0,0 +1 @@",
+ "+function(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "455ba4c6c459945e9e0b6573b760bfc01872bc8b"
+ "shas": "0bdf412036a9a6aea51108a20404c37541fffcfb..c76e13ba716fc18e9924e1f4675845f61823c9c7"
}
,{
"testCaseDescription": "javascript-function-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"function.js"
],
- "sha1": "455ba4c6c459945e9e0b6573b760bfc01872bc8b",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index 2d8d739..4389406 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1 +1,3 @@",
+ "+function(arg1, arg2) { arg1; };",
+ "+function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e35bc26ef80c01c7cdb9df4798e88f65218ef8ce"
+ "shas": "c76e13ba716fc18e9924e1f4675845f61823c9c7..7c1485f22ad0c4bc98a22cdb8d341d2eb97fcab8"
}
,{
"testCaseDescription": "javascript-function-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"function.js"
],
- "sha1": "e35bc26ef80c01c7cdb9df4798e88f65218ef8ce",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index 4389406..924c99e 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function(arg1, arg2) { arg1; };",
+ "+function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5af7a461ecb37a187cb4d0dd737515a509719343"
+ "shas": "7c1485f22ad0c4bc98a22cdb8d341d2eb97fcab8..9e13719e7c1614958c3528e609d7ac1cfb068fe6"
}
,{
"testCaseDescription": "javascript-function-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"function.js"
],
- "sha1": "5af7a461ecb37a187cb4d0dd737515a509719343",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index 924c99e..4389406 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function(arg1, arg2) { arg2; };",
+ "+function(arg1, arg2) { arg1; };",
+ " function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7fcdacc4180764cd579544563fe7d417836107fc"
+ "shas": "9e13719e7c1614958c3528e609d7ac1cfb068fe6..e36301a0b4cc27e38d4c77c49f97e1a6ba816fbb"
}
,{
"testCaseDescription": "javascript-function-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"function.js"
],
- "sha1": "7fcdacc4180764cd579544563fe7d417836107fc",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index 4389406..254dbcf 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function(arg1, arg2) { arg1; };",
+ "-function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg2; };",
+ "+function(arg1, arg2) { arg1; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "835c69b492570d68dca9ae3872aa6b4b6a03711d"
+ "shas": "e36301a0b4cc27e38d4c77c49f97e1a6ba816fbb..fbc7371a528f691d2e0b43ceed413fab19186b82"
}
,{
"testCaseDescription": "javascript-function-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"function.js"
],
- "sha1": "835c69b492570d68dca9ae3872aa6b4b6a03711d",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index 254dbcf..b37e867 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1,2 +1 @@",
+ "-function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg1; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4dca254a8f7653c50a99376f33b14d25f8d8693c"
+ "shas": "fbc7371a528f691d2e0b43ceed413fab19186b82..dd37f0a24f8a677191eb11c1dad4119d46e35d14"
}
,{
"testCaseDescription": "javascript-function-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"function.js"
],
- "sha1": "4dca254a8f7653c50a99376f33b14d25f8d8693c",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index b37e867..e69de29 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1 +0,0 @@",
+ "-function(arg1, arg2) { arg1; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1a65f6b31571ca180a7067af4efe0b804b5bd17f"
+ "shas": "dd37f0a24f8a677191eb11c1dad4119d46e35d14..d700dc51fee7a3dd557906dcdf46d426285d7955"
}]
diff --git a/test/corpus/diff-summaries/javascript/generator-function.json b/test/corpus/diff-summaries/javascript/generator-function.json
index df606301e..7a96187dd 100644
--- a/test/corpus/diff-summaries/javascript/generator-function.json
+++ b/test/corpus/diff-summaries/javascript/generator-function.json
@@ -25,9 +25,16 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "843b9d83e2acc3f1bf014abc4e2402e1a783d3f6",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index e69de29..04e8a59 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -0,0 +1 @@",
+ "+function *generateStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "586ddf785c2a8b750ab5e2e67d4e29b6881a7d11"
+ "shas": "5cab8720cde055f6d78f5c5deaf8980b89a434e1..8ff6dd40a182ab5500d976f04b8d0e919d045ddc"
}
,{
"testCaseDescription": "javascript-generator-function-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "586ddf785c2a8b750ab5e2e67d4e29b6881a7d11",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index 04e8a59..ed5c037 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1 +1,3 @@",
+ "+function *generateNewStuff(arg1, arg2) { yield; yield arg2; };",
+ "+function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9643e5115018e8e937c15f554ff18317207ec7f4"
+ "shas": "8ff6dd40a182ab5500d976f04b8d0e919d045ddc..e3273bce016747d95cbc043e14d23cda41b65129"
}
,{
"testCaseDescription": "javascript-generator-function-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "9643e5115018e8e937c15f554ff18317207ec7f4",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index ed5c037..0895c3f 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function *generateNewStuff(arg1, arg2) { yield; yield arg2; };",
+ "+function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "25ab3575daed7a51443fda5100dd29edf156e2f8"
+ "shas": "e3273bce016747d95cbc043e14d23cda41b65129..3dd2a62eface3915c946a63ecef0c9134bf5b9be"
}
,{
"testCaseDescription": "javascript-generator-function-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "25ab3575daed7a51443fda5100dd29edf156e2f8",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index 0895c3f..ed5c037 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ "+function *generateNewStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2913ec725e62b2faa79bab6d5e99d8b11ecd45c4"
+ "shas": "3dd2a62eface3915c946a63ecef0c9134bf5b9be..9a4d77ff9359a6c8fe9ab42d88157282b742e1be"
}
,{
"testCaseDescription": "javascript-generator-function-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "2913ec725e62b2faa79bab6d5e99d8b11ecd45c4",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index ed5c037..1dae105 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function *generateNewStuff(arg1, arg2) { yield; yield arg2; };",
+ "-function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ "+function *generateNewStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4c912eda971c27f0ba64a9c4cc42508efcca09ad"
+ "shas": "9a4d77ff9359a6c8fe9ab42d88157282b742e1be..63a8b6f6c41bdd248590069ba8f59d53a3b0992f"
}
,{
"testCaseDescription": "javascript-generator-function-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "4c912eda971c27f0ba64a9c4cc42508efcca09ad",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index 1dae105..5846d1c 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1,2 +1 @@",
+ "-function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateNewStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8565f60ebc7b85fb023e32db0bf098e5f9db48cf"
+ "shas": "63a8b6f6c41bdd248590069ba8f59d53a3b0992f..2087f684c9ba7fa39876477f2eacf8b9b12949fa"
}
,{
"testCaseDescription": "javascript-generator-function-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "8565f60ebc7b85fb023e32db0bf098e5f9db48cf",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index 5846d1c..e69de29 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1 +0,0 @@",
+ "-function *generateNewStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "437d13155925d96902bc67c5d88d607d97762adf"
+ "shas": "2087f684c9ba7fa39876477f2eacf8b9b12949fa..973cce7b94116a9e6e8b399f9f0a50bd107fb9b5"
}]
diff --git a/test/corpus/diff-summaries/javascript/identifier.json b/test/corpus/diff-summaries/javascript/identifier.json
index 58f3cbc5b..96570ae7d 100644
--- a/test/corpus/diff-summaries/javascript/identifier.json
+++ b/test/corpus/diff-summaries/javascript/identifier.json
@@ -25,9 +25,16 @@
"filePaths": [
"identifier.js"
],
- "sha1": "e0e3afdc072a442646b858257a8842112c729449",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index e69de29..1cf4ad0 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -0,0 +1 @@",
+ "+theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7d5c31114093f1169f023a98ed1b141aed1020a4"
+ "shas": "2642fef686808ac2a6c5edde323e87257f4f2983..369e63ae9927770fe9ca2fd662ca648e43ab72e5"
}
,{
"testCaseDescription": "javascript-identifier-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"identifier.js"
],
- "sha1": "7d5c31114093f1169f023a98ed1b141aed1020a4",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index 1cf4ad0..888855a 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1 +1,3 @@",
+ "+theVar2",
+ "+theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "23e48376eafe46181894d00f9ab5ddbdfa250c35"
+ "shas": "369e63ae9927770fe9ca2fd662ca648e43ab72e5..ee416c16400890b8f6351b1c8113657cb7671eb7"
}
,{
"testCaseDescription": "javascript-identifier-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"identifier.js"
],
- "sha1": "23e48376eafe46181894d00f9ab5ddbdfa250c35",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index 888855a..60e041c 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1,3 +1,3 @@",
+ "-theVar2",
+ "+theVar;",
+ " theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "dd258400725f6814173e344e4273a17edaa1974d"
+ "shas": "ee416c16400890b8f6351b1c8113657cb7671eb7..13d808ca205317e4c1b13c036517ed17cdde1da3"
}
,{
"testCaseDescription": "javascript-identifier-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"identifier.js"
],
- "sha1": "dd258400725f6814173e344e4273a17edaa1974d",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index 60e041c..888855a 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1,3 +1,3 @@",
+ "-theVar;",
+ "+theVar2",
+ " theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c7c6fa74ce3bbcfd516baa8794504835aef30d24"
+ "shas": "13d808ca205317e4c1b13c036517ed17cdde1da3..1f1988b798d7bd2558d1d050b242ef4afbd52629"
}
,{
"testCaseDescription": "javascript-identifier-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"identifier.js"
],
- "sha1": "c7c6fa74ce3bbcfd516baa8794504835aef30d24",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index 888855a..fbc7b28 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1,3 +1,2 @@",
+ "-theVar2",
+ "-theVar;",
+ " theVar;",
+ "+theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "01a282ae6900beefd7af33d2e0e16dbde0ee755c"
+ "shas": "1f1988b798d7bd2558d1d050b242ef4afbd52629..6408b95d2773e060ccc2c624b319447b326c8a51"
}
,{
"testCaseDescription": "javascript-identifier-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"identifier.js"
],
- "sha1": "01a282ae6900beefd7af33d2e0e16dbde0ee755c",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index fbc7b28..7276d95 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1,2 +1 @@",
+ "-theVar;",
+ " theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3226b408c1def23bb83ecccadebfb8f845871e60"
+ "shas": "6408b95d2773e060ccc2c624b319447b326c8a51..011d19e2d6ea45758e3df50809069437b44911b5"
}
,{
"testCaseDescription": "javascript-identifier-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"identifier.js"
],
- "sha1": "3226b408c1def23bb83ecccadebfb8f845871e60",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index 7276d95..e69de29 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1 +0,0 @@",
+ "-theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b3470025ee263454110f25252e09c359560d1bd5"
+ "shas": "011d19e2d6ea45758e3df50809069437b44911b5..5180fa74c7ae39b3c2cb94b9b5498307af385e5c"
}]
diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json
index 1b852febb..2471cd96f 100644
--- a/test/corpus/diff-summaries/javascript/if-else.json
+++ b/test/corpus/diff-summaries/javascript/if-else.json
@@ -25,9 +25,16 @@
"filePaths": [
"if-else.js"
],
- "sha1": "54d43b3c10fed335e753e25a550cd47511bf14e1",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index e69de29..d81ebad 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -0,0 +1 @@",
+ "+if (x) y; else if (a) b; else if (c) d; else if (e) f; else g"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "650c28440a549f6362cfbf568c8b446a1903c958"
+ "shas": "ee538d5b471190fe27f80e1defc319f36f5f9c38..d5f532daeb84c4dd664519d388575b8891e7e25a"
}
,{
"testCaseDescription": "javascript-if-else-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"if-else.js"
],
- "sha1": "650c28440a549f6362cfbf568c8b446a1903c958",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index d81ebad..6bb0eaa 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1 +1,3 @@",
+ "+if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o",
+ "+if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "20c59882c320fb6791c0c529a947330214303d24"
+ "shas": "d5f532daeb84c4dd664519d388575b8891e7e25a..539d5f1eb9ec34131ed8d31c596c38285f83e6bf"
}
,{
"testCaseDescription": "javascript-if-else-delete-insert-test",
@@ -105,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'g' identifier with the 'x' identifier"
+ "summary": "Replaced the 'g' identifier with the 'x' identifier in the 'x' if statement"
},
{
"span": {
@@ -132,7 +148,7 @@
}
]
},
- "summary": "Replaced the 'h' identifier with the 'y' identifier"
+ "summary": "Replaced the 'h' identifier with the 'y' identifier in the 'x' if statement"
},
{
"span": {
@@ -159,7 +175,7 @@
}
]
},
- "summary": "Replaced the 'i' identifier with the 'a' identifier"
+ "summary": "Replaced the 'i' identifier with the 'a' identifier in the 'a' if statement"
},
{
"span": {
@@ -174,7 +190,7 @@
]
}
},
- "summary": "Added the 'b' identifier"
+ "summary": "Added the 'b' identifier in the 'a' if statement"
},
{
"span": {
@@ -189,7 +205,7 @@
]
}
},
- "summary": "Deleted the 'j' identifier"
+ "summary": "Deleted the 'j' identifier in the 'a' if statement"
},
{
"span": {
@@ -216,7 +232,7 @@
}
]
},
- "summary": "Replaced the 'k' identifier with the 'c' identifier"
+ "summary": "Replaced the 'k' identifier with the 'c' identifier in the 'c' if statement"
},
{
"span": {
@@ -243,7 +259,7 @@
}
]
},
- "summary": "Replaced the 'l' identifier with the 'd' identifier"
+ "summary": "Replaced the 'l' identifier with the 'd' identifier in the 'c' if statement"
},
{
"span": {
@@ -270,7 +286,7 @@
}
]
},
- "summary": "Replaced the 'm' identifier with the 'e' identifier"
+ "summary": "Replaced the 'm' identifier with the 'e' identifier in the 'e' if statement"
},
{
"span": {
@@ -285,7 +301,7 @@
]
}
},
- "summary": "Added the 'f' identifier"
+ "summary": "Added the 'f' identifier in the 'e' if statement"
},
{
"span": {
@@ -300,7 +316,7 @@
]
}
},
- "summary": "Deleted the 'n' identifier"
+ "summary": "Deleted the 'n' identifier in the 'e' if statement"
},
{
"span": {
@@ -327,7 +343,7 @@
}
]
},
- "summary": "Replaced the 'o' identifier with the 'g' identifier"
+ "summary": "Replaced the 'o' identifier with the 'g' identifier in the 'e' if statement"
}
]
},
@@ -336,9 +352,19 @@
"filePaths": [
"if-else.js"
],
- "sha1": "20c59882c320fb6791c0c529a947330214303d24",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index 6bb0eaa..2034be1 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1,3 +1,3 @@",
+ "-if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o",
+ "+if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fbf74c5787cd8b79a2cc6be34bf3908549621cdb"
+ "shas": "539d5f1eb9ec34131ed8d31c596c38285f83e6bf..f525e3671aa6d43caf17c2582f3c746f07570b7a"
}
,{
"testCaseDescription": "javascript-if-else-replacement-test",
@@ -370,7 +396,7 @@
}
]
},
- "summary": "Replaced the 'x' identifier with the 'g' identifier"
+ "summary": "Replaced the 'x' identifier with the 'g' identifier in the 'g' if statement"
},
{
"span": {
@@ -397,7 +423,7 @@
}
]
},
- "summary": "Replaced the 'y' identifier with the 'h' identifier"
+ "summary": "Replaced the 'y' identifier with the 'h' identifier in the 'g' if statement"
},
{
"span": {
@@ -424,7 +450,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'i' identifier"
+ "summary": "Replaced the 'a' identifier with the 'i' identifier in the 'i' if statement"
},
{
"span": {
@@ -439,7 +465,7 @@
]
}
},
- "summary": "Added the 'j' identifier"
+ "summary": "Added the 'j' identifier in the 'i' if statement"
},
{
"span": {
@@ -454,7 +480,7 @@
]
}
},
- "summary": "Deleted the 'b' identifier"
+ "summary": "Deleted the 'b' identifier in the 'i' if statement"
},
{
"span": {
@@ -481,7 +507,7 @@
}
]
},
- "summary": "Replaced the 'c' identifier with the 'k' identifier"
+ "summary": "Replaced the 'c' identifier with the 'k' identifier in the 'k' if statement"
},
{
"span": {
@@ -508,7 +534,7 @@
}
]
},
- "summary": "Replaced the 'd' identifier with the 'l' identifier"
+ "summary": "Replaced the 'd' identifier with the 'l' identifier in the 'k' if statement"
},
{
"span": {
@@ -535,7 +561,7 @@
}
]
},
- "summary": "Replaced the 'e' identifier with the 'm' identifier"
+ "summary": "Replaced the 'e' identifier with the 'm' identifier in the 'm' if statement"
},
{
"span": {
@@ -550,7 +576,7 @@
]
}
},
- "summary": "Added the 'n' identifier"
+ "summary": "Added the 'n' identifier in the 'm' if statement"
},
{
"span": {
@@ -565,7 +591,7 @@
]
}
},
- "summary": "Deleted the 'f' identifier"
+ "summary": "Deleted the 'f' identifier in the 'm' if statement"
},
{
"span": {
@@ -592,7 +618,7 @@
}
]
},
- "summary": "Replaced the 'g' identifier with the 'o' identifier"
+ "summary": "Replaced the 'g' identifier with the 'o' identifier in the 'm' if statement"
}
]
},
@@ -601,9 +627,19 @@
"filePaths": [
"if-else.js"
],
- "sha1": "fbf74c5787cd8b79a2cc6be34bf3908549621cdb",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index 2034be1..6bb0eaa 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1,3 +1,3 @@",
+ "-if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ "+if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6b56fa332a9b893353bd4ab5acfe375b4b478cc6"
+ "shas": "f525e3671aa6d43caf17c2582f3c746f07570b7a..9fce9df9688253990d3fcfa4eb8f2280aa1c0c7c"
}
,{
"testCaseDescription": "javascript-if-else-delete-replacement-test",
@@ -662,9 +698,19 @@
"filePaths": [
"if-else.js"
],
- "sha1": "6b56fa332a9b893353bd4ab5acfe375b4b478cc6",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index 6bb0eaa..e26d6c4 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1,3 +1,2 @@",
+ "-if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o",
+ "-if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ "+if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "29013b75d9d4db569f8d4f1641d87dd973724eae"
+ "shas": "9fce9df9688253990d3fcfa4eb8f2280aa1c0c7c..f5b900cb596f7084a32ca9441f01e9be4b1e27dd"
}
,{
"testCaseDescription": "javascript-if-else-delete-test",
@@ -693,9 +739,17 @@
"filePaths": [
"if-else.js"
],
- "sha1": "29013b75d9d4db569f8d4f1641d87dd973724eae",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index e26d6c4..1a55d0b 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1,2 +1 @@",
+ "-if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "279becd75ae220a302f98e5f9360e948ab2dd01c"
+ "shas": "f5b900cb596f7084a32ca9441f01e9be4b1e27dd..c3bb4c6e35fc4755d18a5e0fb53d5410a476c039"
}
,{
"testCaseDescription": "javascript-if-else-delete-rest-test",
@@ -724,7 +778,14 @@
"filePaths": [
"if-else.js"
],
- "sha1": "279becd75ae220a302f98e5f9360e948ab2dd01c",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index 1a55d0b..e69de29 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1 +0,0 @@",
+ "-if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2dee917afc37bf88e9b7405744f9b8877a4c68c3"
+ "shas": "c3bb4c6e35fc4755d18a5e0fb53d5410a476c039..dffe792710a5ad52de12ed62e48340a71e5c9227"
}]
diff --git a/test/corpus/diff-summaries/javascript/if.json b/test/corpus/diff-summaries/javascript/if.json
index 12f5203a2..a4fd0fa51 100644
--- a/test/corpus/diff-summaries/javascript/if.json
+++ b/test/corpus/diff-summaries/javascript/if.json
@@ -25,9 +25,16 @@
"filePaths": [
"if.js"
],
- "sha1": "dc9aa0f5ce2176319c7eb9475db8787876afb4d9",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index e69de29..52d4b4f 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -0,0 +1 @@",
+ "+if (x) { log(y); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "69f411176d7219c08562a4cb0d8c4eca25694610"
+ "shas": "4951403c16600a8ebe50779236bcbc480c823807..3ab04d08f09b5d896597f687046696c6cec1cf08"
}
,{
"testCaseDescription": "javascript-if-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"if.js"
],
- "sha1": "69f411176d7219c08562a4cb0d8c4eca25694610",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index 52d4b4f..ae4ee32 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1 +1,3 @@",
+ "+if (a.b) { log(c); d; }",
+ "+if (x) { log(y); }",
+ " if (x) { log(y); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c429c8c2238a29d93ae024dc83871a5fec81e9bb"
+ "shas": "3ab04d08f09b5d896597f687046696c6cec1cf08..c5c2097ab589ca6e4187e2bae6455468ececcb93"
}
,{
"testCaseDescription": "javascript-if-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"if.js"
],
- "sha1": "c429c8c2238a29d93ae024dc83871a5fec81e9bb",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index ae4ee32..df55832 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1,3 +1,3 @@",
+ "-if (a.b) { log(c); d; }",
+ "+if (x) { log(y); }",
+ " if (x) { log(y); }",
+ " if (x) { log(y); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8dfaa25d65e0850b25ac1fe3518e33d227f4400b"
+ "shas": "c5c2097ab589ca6e4187e2bae6455468ececcb93..2f37518e72e7f3ea87111886870a575d8dc4369a"
}
,{
"testCaseDescription": "javascript-if-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"if.js"
],
- "sha1": "8dfaa25d65e0850b25ac1fe3518e33d227f4400b",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index df55832..ae4ee32 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1,3 +1,3 @@",
+ "-if (x) { log(y); }",
+ "+if (a.b) { log(c); d; }",
+ " if (x) { log(y); }",
+ " if (x) { log(y); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c883527a3f28132042272cd97a8d0df1a7979ab6"
+ "shas": "2f37518e72e7f3ea87111886870a575d8dc4369a..3eaefb1b0937e7789aac874832358df33b530310"
}
,{
"testCaseDescription": "javascript-if-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"if.js"
],
- "sha1": "c883527a3f28132042272cd97a8d0df1a7979ab6",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index ae4ee32..38b83ef 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1,3 +1,2 @@",
+ "-if (a.b) { log(c); d; }",
+ "-if (x) { log(y); }",
+ " if (x) { log(y); }",
+ "+if (a.b) { log(c); d; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "71c0d8d6182309053691d133c3110dd9c9690fef"
+ "shas": "3eaefb1b0937e7789aac874832358df33b530310..0e72c4d71d418eefb3726b7e5bc0232a5aad7db6"
}
,{
"testCaseDescription": "javascript-if-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"if.js"
],
- "sha1": "71c0d8d6182309053691d133c3110dd9c9690fef",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index 38b83ef..f67163b 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1,2 +1 @@",
+ "-if (x) { log(y); }",
+ " if (a.b) { log(c); d; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8c3981d5ce473f0be35cdd782df52ac7c8597fc0"
+ "shas": "0e72c4d71d418eefb3726b7e5bc0232a5aad7db6..b81dbad2ec8358dd3e22e71cca5eea1c286769a8"
}
,{
"testCaseDescription": "javascript-if-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"if.js"
],
- "sha1": "8c3981d5ce473f0be35cdd782df52ac7c8597fc0",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index f67163b..e69de29 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1 +0,0 @@",
+ "-if (a.b) { log(c); d; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "54d43b3c10fed335e753e25a550cd47511bf14e1"
+ "shas": "b81dbad2ec8358dd3e22e71cca5eea1c286769a8..ee538d5b471190fe27f80e1defc319f36f5f9c38"
}]
diff --git a/test/corpus/diff-summaries/javascript/import.json b/test/corpus/diff-summaries/javascript/import.json
index d45ad3d12..0677c4d8f 100644
--- a/test/corpus/diff-summaries/javascript/import.json
+++ b/test/corpus/diff-summaries/javascript/import.json
@@ -130,9 +130,23 @@
"filePaths": [
"import.js"
],
- "sha1": "1011ea99d2c513437073a38030c1290fcc06cac4",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index e69de29..491cb15 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -0,0 +1,8 @@",
+ "+import defaultMember from \"foo\";",
+ "+import * as name from \"aardvark\";",
+ "+import { member } from \"ant\";",
+ "+import { member1 , member2 } from \"antelope\";",
+ "+import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "+import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "+import defaultMember, * as name from \"alligator\";",
+ "+import \"arctic-tern\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "40bc61d9d0c547e336e8a44b5e90f7db3c90f585"
+ "shas": "94d7e0ef831c81697b130d8e7c032b876c270e33..bddd7205c75f938fdef876cad00d2a3130c8a056"
}
,{
"testCaseDescription": "javascript-import-replacement-insert-test",
@@ -386,9 +400,34 @@
"filePaths": [
"import.js"
],
- "sha1": "40bc61d9d0c547e336e8a44b5e90f7db3c90f585",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index 491cb15..045c536 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,3 +1,19 @@",
+ "+import defaultMember from \"babirusa\";",
+ "+import * as otherName from \"baboon\";",
+ "+import { element } from \"badger\";",
+ "+import { element1 , element2 } from \"bald-eagle\";",
+ "+import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "+import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "+import defaultMember, * as element from \"barbet\";",
+ "+import \"basilisk\";",
+ "+import defaultMember from \"foo\";",
+ "+import * as name from \"aardvark\";",
+ "+import { member } from \"ant\";",
+ "+import { member1 , member2 } from \"antelope\";",
+ "+import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "+import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "+import defaultMember, * as name from \"alligator\";",
+ "+import \"arctic-tern\";",
+ " import defaultMember from \"foo\";",
+ " import * as name from \"aardvark\";",
+ " import { member } from \"ant\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "433f5cbcd86af87576fdb9ec6b2d9851f5632d4d"
+ "shas": "bddd7205c75f938fdef876cad00d2a3130c8a056..2f4516215b92d79082b1f806ec0ac74a2e18726c"
}
,{
"testCaseDescription": "javascript-import-delete-insert-test",
@@ -660,9 +699,34 @@
"filePaths": [
"import.js"
],
- "sha1": "433f5cbcd86af87576fdb9ec6b2d9851f5632d4d",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index 045c536..cbad5a4 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,11 +1,11 @@",
+ "-import defaultMember from \"babirusa\";",
+ "-import * as otherName from \"baboon\";",
+ "-import { element } from \"badger\";",
+ "-import { element1 , element2 } from \"bald-eagle\";",
+ "-import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "-import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "-import defaultMember, * as element from \"barbet\";",
+ "-import \"basilisk\";",
+ "+import defaultMember from \"foo\";",
+ "+import * as name from \"aardvark\";",
+ "+import { member } from \"ant\";",
+ "+import { member1 , member2 } from \"antelope\";",
+ "+import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "+import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "+import defaultMember, * as name from \"alligator\";",
+ "+import \"arctic-tern\";",
+ " import defaultMember from \"foo\";",
+ " import * as name from \"aardvark\";",
+ " import { member } from \"ant\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fd76bae4b8cceb60c08b9f3c5cad5c89e5f9794e"
+ "shas": "2f4516215b92d79082b1f806ec0ac74a2e18726c..f6b32da510dd536120c67a2e13e3c5f17ca08a62"
}
,{
"testCaseDescription": "javascript-import-replacement-test",
@@ -934,9 +998,34 @@
"filePaths": [
"import.js"
],
- "sha1": "fd76bae4b8cceb60c08b9f3c5cad5c89e5f9794e",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index cbad5a4..045c536 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,11 +1,11 @@",
+ "-import defaultMember from \"foo\";",
+ "-import * as name from \"aardvark\";",
+ "-import { member } from \"ant\";",
+ "-import { member1 , member2 } from \"antelope\";",
+ "-import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "-import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "-import defaultMember, * as name from \"alligator\";",
+ "-import \"arctic-tern\";",
+ "+import defaultMember from \"babirusa\";",
+ "+import * as otherName from \"baboon\";",
+ "+import { element } from \"badger\";",
+ "+import { element1 , element2 } from \"bald-eagle\";",
+ "+import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "+import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "+import defaultMember, * as element from \"barbet\";",
+ "+import \"basilisk\";",
+ " import defaultMember from \"foo\";",
+ " import * as name from \"aardvark\";",
+ " import { member } from \"ant\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2dd6289f8d933a4704f37ac94ddf156032a92a00"
+ "shas": "f6b32da510dd536120c67a2e13e3c5f17ca08a62..9d51ffb2d1950579de47c825eca14557ae9cefc8"
}
,{
"testCaseDescription": "javascript-import-delete-replacement-test",
@@ -1310,9 +1399,46 @@
"filePaths": [
"import.js"
],
- "sha1": "2dd6289f8d933a4704f37ac94ddf156032a92a00",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index 045c536..873ff75 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,19 +1,3 @@",
+ "-import defaultMember from \"babirusa\";",
+ "-import * as otherName from \"baboon\";",
+ "-import { element } from \"badger\";",
+ "-import { element1 , element2 } from \"bald-eagle\";",
+ "-import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "-import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "-import defaultMember, * as element from \"barbet\";",
+ "-import \"basilisk\";",
+ "-import defaultMember from \"foo\";",
+ "-import * as name from \"aardvark\";",
+ "-import { member } from \"ant\";",
+ "-import { member1 , member2 } from \"antelope\";",
+ "-import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "-import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "-import defaultMember, * as name from \"alligator\";",
+ "-import \"arctic-tern\";",
+ " import defaultMember from \"foo\";",
+ " import * as name from \"aardvark\";",
+ " import { member } from \"ant\";",
+ "@@ -22,3 +6,11 @@ import { member1 , member2 as alias2 } from \"ant-eater\";",
+ " import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ " import defaultMember, * as name from \"alligator\";",
+ " import \"arctic-tern\";",
+ "+import defaultMember from \"babirusa\";",
+ "+import * as otherName from \"baboon\";",
+ "+import { element } from \"badger\";",
+ "+import { element1 , element2 } from \"bald-eagle\";",
+ "+import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "+import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "+import defaultMember, * as element from \"barbet\";",
+ "+import \"basilisk\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1719ae08e72d065a121f9a962a48b33288f90868"
+ "shas": "9d51ffb2d1950579de47c825eca14557ae9cefc8..d8a44ed18d0fd2d59c8bfff2e97409d01face666"
}
,{
"testCaseDescription": "javascript-import-delete-test",
@@ -1446,9 +1572,26 @@
"filePaths": [
"import.js"
],
- "sha1": "1719ae08e72d065a121f9a962a48b33288f90868",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index 873ff75..db72339 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,11 +1,3 @@",
+ "-import defaultMember from \"foo\";",
+ "-import * as name from \"aardvark\";",
+ "-import { member } from \"ant\";",
+ "-import { member1 , member2 } from \"antelope\";",
+ "-import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "-import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "-import defaultMember, * as name from \"alligator\";",
+ "-import \"arctic-tern\";",
+ " import defaultMember from \"babirusa\";",
+ " import * as otherName from \"baboon\";",
+ " import { element } from \"badger\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "193d82337dbb90df9252043dea7fe42e407ccc0e"
+ "shas": "d8a44ed18d0fd2d59c8bfff2e97409d01face666..b5659554207c6b66f77467f2277c99b1686f8e02"
}
,{
"testCaseDescription": "javascript-import-delete-rest-test",
@@ -1582,7 +1725,21 @@
"filePaths": [
"import.js"
],
- "sha1": "193d82337dbb90df9252043dea7fe42e407ccc0e",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index db72339..e69de29 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,8 +0,0 @@",
+ "-import defaultMember from \"babirusa\";",
+ "-import * as otherName from \"baboon\";",
+ "-import { element } from \"badger\";",
+ "-import { element1 , element2 } from \"bald-eagle\";",
+ "-import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "-import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "-import defaultMember, * as element from \"barbet\";",
+ "-import \"basilisk\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7b67ddbc527cc15d1cbac33725dc0c4d79472c8c"
+ "shas": "b5659554207c6b66f77467f2277c99b1686f8e02..0eb14098d9cfc48fe7ffb44e37c71cb6cb58c878"
}]
diff --git a/test/corpus/diff-summaries/javascript/math-assignment-operator.json b/test/corpus/diff-summaries/javascript/math-assignment-operator.json
index 9b5a33ee4..1d72972f3 100644
--- a/test/corpus/diff-summaries/javascript/math-assignment-operator.json
+++ b/test/corpus/diff-summaries/javascript/math-assignment-operator.json
@@ -25,9 +25,16 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "cf3bb492593b241390a7cfd11dbdbd3d251a4177",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index e69de29..7150d6e 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -0,0 +1 @@",
+ "+x += 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5e3008d3df1c58d4ffb6fc9245ba0c50d5ad50e5"
+ "shas": "5da04c6d20aa6fdedbc205bf855829ccd10687f3..5ec631f6610cf3cc1f773396df8e13b4b814129c"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "5e3008d3df1c58d4ffb6fc9245ba0c50d5ad50e5",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index 7150d6e..0bf97e7 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1 +1,3 @@",
+ "+x += 2;",
+ "+x += 1;",
+ " x += 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8437fbfaf6631316f57d0d1c1a72f2e3922f393d"
+ "shas": "5ec631f6610cf3cc1f773396df8e13b4b814129c..b0a185f38a22e6745bb368f017c102214337c4cb"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "8437fbfaf6631316f57d0d1c1a72f2e3922f393d",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index 0bf97e7..ad04937 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-x += 2;",
+ "+x += 1;",
+ " x += 1;",
+ " x += 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b40e39c6b8bb1409ba0d98c4479e37d7467f7ee6"
+ "shas": "b0a185f38a22e6745bb368f017c102214337c4cb..38cc878f5583067ae28923541b036488434aff2b"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "b40e39c6b8bb1409ba0d98c4479e37d7467f7ee6",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index ad04937..0bf97e7 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-x += 1;",
+ "+x += 2;",
+ " x += 1;",
+ " x += 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "392a9f0d59a7bf5d3b18769cd84c20687b82ac4a"
+ "shas": "38cc878f5583067ae28923541b036488434aff2b..156edc8d14ab30f0157138c24b7694cec8a4bb67"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "392a9f0d59a7bf5d3b18769cd84c20687b82ac4a",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index 0bf97e7..7127545 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-x += 2;",
+ "-x += 1;",
+ " x += 1;",
+ "+x += 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b6960087a76266fca12fa88acfce88a499a43397"
+ "shas": "156edc8d14ab30f0157138c24b7694cec8a4bb67..185343b45e80feb8176e8a5a0ee4ec9bbe0fb637"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "b6960087a76266fca12fa88acfce88a499a43397",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index 7127545..94d1472 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1,2 +1 @@",
+ "-x += 1;",
+ " x += 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "04d6487122e380aaa06d6fceb345e3a36f0e749a"
+ "shas": "185343b45e80feb8176e8a5a0ee4ec9bbe0fb637..8ff3bab42e216d76eeba9d8c9c04f66c9c99eb7d"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "04d6487122e380aaa06d6fceb345e3a36f0e749a",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index 94d1472..e69de29 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1 +0,0 @@",
+ "-x += 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d42f86b317b470d5207108107a9710b5a66b7693"
+ "shas": "8ff3bab42e216d76eeba9d8c9c04f66c9c99eb7d..1c2dbb18fb6fc930b3d0e6bb31a559a853be5c63"
}]
diff --git a/test/corpus/diff-summaries/javascript/math-operator.json b/test/corpus/diff-summaries/javascript/math-operator.json
index 8b5b936b5..13e75eb52 100644
--- a/test/corpus/diff-summaries/javascript/math-operator.json
+++ b/test/corpus/diff-summaries/javascript/math-operator.json
@@ -25,9 +25,16 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "012105d0edaef241c26098d6e1680dab22bacbbc",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index e69de29..0344667 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -0,0 +1 @@",
+ "+i + j * 3 - j % 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5098eaf4a2d14d5002b653133b243ec1ea36e0a6"
+ "shas": "41ab7cb7dc378bf229f7a08f1a03c0676483f435..1571de07c19283348c86a4d81f61c63270a37d3f"
}
,{
"testCaseDescription": "javascript-math-operator-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "5098eaf4a2d14d5002b653133b243ec1ea36e0a6",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index 0344667..79f5f20 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1 +1,3 @@",
+ "+i + j * 2 - j % 4;",
+ "+i + j * 3 - j % 5;",
+ " i + j * 3 - j % 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "44d7073ad770d7db6888b668d150cae2288ab60f"
+ "shas": "1571de07c19283348c86a4d81f61c63270a37d3f..97979c27333f35afb7288063c45a2f25cf5e1808"
}
,{
"testCaseDescription": "javascript-math-operator-delete-insert-test",
@@ -141,9 +157,19 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "44d7073ad770d7db6888b668d150cae2288ab60f",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index 79f5f20..284561c 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i + j * 2 - j % 4;",
+ "+i + j * 3 - j % 5;",
+ " i + j * 3 - j % 5;",
+ " i + j * 3 - j % 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1a22b412a511ec382bb6930aa92007e097c5031e"
+ "shas": "97979c27333f35afb7288063c45a2f25cf5e1808..d8320eb8219fb470d6ac17996f9d74b61fe7e6ee"
}
,{
"testCaseDescription": "javascript-math-operator-replacement-test",
@@ -211,9 +237,19 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "1a22b412a511ec382bb6930aa92007e097c5031e",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index 284561c..79f5f20 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i + j * 3 - j % 5;",
+ "+i + j * 2 - j % 4;",
+ " i + j * 3 - j % 5;",
+ " i + j * 3 - j % 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "02f4915a4e73427c0982a2981df44a07f162a3dd"
+ "shas": "d8320eb8219fb470d6ac17996f9d74b61fe7e6ee..ca05a18c434755562d8787734dd2aa347af4ffca"
}
,{
"testCaseDescription": "javascript-math-operator-delete-replacement-test",
@@ -272,9 +308,19 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "02f4915a4e73427c0982a2981df44a07f162a3dd",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index 79f5f20..d1055f7 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-i + j * 2 - j % 4;",
+ "-i + j * 3 - j % 5;",
+ " i + j * 3 - j % 5;",
+ "+i + j * 2 - j % 4;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "66f958a4880c2ba4f36c4df0f3b7941a0a958408"
+ "shas": "ca05a18c434755562d8787734dd2aa347af4ffca..4f0d2886b18d7b66ad3b3d0222b5c4040ebfbf05"
}
,{
"testCaseDescription": "javascript-math-operator-delete-test",
@@ -303,9 +349,17 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "66f958a4880c2ba4f36c4df0f3b7941a0a958408",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index d1055f7..79ba2b3 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1,2 +1 @@",
+ "-i + j * 3 - j % 5;",
+ " i + j * 2 - j % 4;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6c30506adfccd4e508ef479cdbfd0772ef191fd9"
+ "shas": "4f0d2886b18d7b66ad3b3d0222b5c4040ebfbf05..c7c1c352742d04515a004d1c08642b78cf1e83cf"
}
,{
"testCaseDescription": "javascript-math-operator-delete-rest-test",
@@ -334,7 +388,14 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "6c30506adfccd4e508ef479cdbfd0772ef191fd9",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index 79ba2b3..e69de29 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1 +0,0 @@",
+ "-i + j * 2 - j % 4;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0f277a98ca88f6c1e02d2811fa15b32c1909edf0"
+ "shas": "c7c1c352742d04515a004d1c08642b78cf1e83cf..69248e3fdb3e6ab7da864ef7bd3a915aeefd3cc4"
}]
diff --git a/test/corpus/diff-summaries/javascript/member-access-assignment.json b/test/corpus/diff-summaries/javascript/member-access-assignment.json
index ef8afb83c..797cabc82 100644
--- a/test/corpus/diff-summaries/javascript/member-access-assignment.json
+++ b/test/corpus/diff-summaries/javascript/member-access-assignment.json
@@ -25,9 +25,16 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "45a5360969a82ef1602c4fd2629a242bd75a1edf",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index e69de29..7a99e30 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -0,0 +1 @@",
+ "+y.x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8765d002f676f7054f0639dedf551abd07ffe542"
+ "shas": "83f3153b76f49e077237997c965dc6f3c3a159bc..e3b5bd418d494825d815573a2dd33bb71bee5d48"
}
,{
"testCaseDescription": "javascript-member-access-assignment-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "8765d002f676f7054f0639dedf551abd07ffe542",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 7a99e30..3204006 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1 +1,3 @@",
+ "+y.x = 1;",
+ "+y.x = 0;",
+ " y.x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9c2a1db0fae9b9a45b97e622cc42f4290679e8c6"
+ "shas": "e3b5bd418d494825d815573a2dd33bb71bee5d48..1da355d7b96efcfa960001b22e4bc94e5be102bd"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "9c2a1db0fae9b9a45b97e622cc42f4290679e8c6",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 3204006..94893a3 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-y.x = 1;",
+ "+y.x = 0;",
+ " y.x = 0;",
+ " y.x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f2ba98a2189e8e9a03a40c5de8b6e2965ba598e2"
+ "shas": "1da355d7b96efcfa960001b22e4bc94e5be102bd..f2443f2327ec99428bb7538077575ea11136f8bd"
}
,{
"testCaseDescription": "javascript-member-access-assignment-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "f2ba98a2189e8e9a03a40c5de8b6e2965ba598e2",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 94893a3..3204006 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-y.x = 0;",
+ "+y.x = 1;",
+ " y.x = 0;",
+ " y.x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "acd420ac3e3fd87da90be56d4e9c3f4dd7159d78"
+ "shas": "f2443f2327ec99428bb7538077575ea11136f8bd..396adf86163adae31b6cbe282ed485497c4f42a4"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "acd420ac3e3fd87da90be56d4e9c3f4dd7159d78",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 3204006..8d78a24 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1,3 +1,2 @@",
+ "-y.x = 1;",
+ "-y.x = 0;",
+ " y.x = 0;",
+ "+y.x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "92a6f737b4ae488f87a9b653899cabd2f7040a8e"
+ "shas": "396adf86163adae31b6cbe282ed485497c4f42a4..ebd783b11d81b4c31d3883606aa0ee7019afb1c3"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "92a6f737b4ae488f87a9b653899cabd2f7040a8e",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 8d78a24..799018d 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1,2 +1 @@",
+ "-y.x = 0;",
+ " y.x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e3455e03e05976466cf133e6def4b5e4dd884ba7"
+ "shas": "ebd783b11d81b4c31d3883606aa0ee7019afb1c3..f0a86404c7e04e9a627fd8464879a14361a379bd"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "e3455e03e05976466cf133e6def4b5e4dd884ba7",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 799018d..e69de29 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1 +0,0 @@",
+ "-y.x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "05616ce185cfef047b0a9726d34dc39afb476f00"
+ "shas": "f0a86404c7e04e9a627fd8464879a14361a379bd..faf582893e706ae259a0482d65d424fbcf137bb2"
}]
diff --git a/test/corpus/diff-summaries/javascript/member-access.json b/test/corpus/diff-summaries/javascript/member-access.json
index 06356627d..186a73d2c 100644
--- a/test/corpus/diff-summaries/javascript/member-access.json
+++ b/test/corpus/diff-summaries/javascript/member-access.json
@@ -25,9 +25,16 @@
"filePaths": [
"member-access.js"
],
- "sha1": "00c3afcb0bf345232b8117cd6726492a096d4c5a",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index e69de29..3c837c9 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -0,0 +1 @@",
+ "+x.someProperty;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4012ca981630076b37c5b20c17b61e31a98e736c"
+ "shas": "0cbc55e481f01ab536c7832c5ebbc21d7f9e9021..9a5f4f1bbfa04d4b229b51802ca72129a31b1953"
}
,{
"testCaseDescription": "javascript-member-access-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"member-access.js"
],
- "sha1": "4012ca981630076b37c5b20c17b61e31a98e736c",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 3c837c9..858131a 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1 +1,3 @@",
+ "+x.someOtherProperty",
+ "+x.someProperty;",
+ " x.someProperty;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3ca0614bd090cac0b08aa17bb7eb1aac488a8681"
+ "shas": "9a5f4f1bbfa04d4b229b51802ca72129a31b1953..93677ca22426294b752c658707b4052a3a3220ed"
}
,{
"testCaseDescription": "javascript-member-access-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"member-access.js"
],
- "sha1": "3ca0614bd090cac0b08aa17bb7eb1aac488a8681",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 858131a..5ed8a8d 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1,3 +1,3 @@",
+ "-x.someOtherProperty",
+ "+x.someProperty;",
+ " x.someProperty;",
+ " x.someProperty;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c066db999bc7bb13d01702bd53263b18e1af3da6"
+ "shas": "93677ca22426294b752c658707b4052a3a3220ed..df73936014819634cde8e6741fef45116b094d93"
}
,{
"testCaseDescription": "javascript-member-access-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"member-access.js"
],
- "sha1": "c066db999bc7bb13d01702bd53263b18e1af3da6",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 5ed8a8d..858131a 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1,3 +1,3 @@",
+ "-x.someProperty;",
+ "+x.someOtherProperty",
+ " x.someProperty;",
+ " x.someProperty;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "96988bb802db16817c452669fa0a715dadfb0e8a"
+ "shas": "df73936014819634cde8e6741fef45116b094d93..94c28d92c27008e7f21ed463e683fdfbda0b8287"
}
,{
"testCaseDescription": "javascript-member-access-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"member-access.js"
],
- "sha1": "96988bb802db16817c452669fa0a715dadfb0e8a",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 858131a..81f5f46 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1,3 +1,2 @@",
+ "-x.someOtherProperty",
+ "-x.someProperty;",
+ " x.someProperty;",
+ "+x.someOtherProperty"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "cdc91909a89d63ae08b39ff4d6787bad3001c54a"
+ "shas": "94c28d92c27008e7f21ed463e683fdfbda0b8287..38ee25545f8644cee42edb45ef2f7b29b26892d5"
}
,{
"testCaseDescription": "javascript-member-access-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"member-access.js"
],
- "sha1": "cdc91909a89d63ae08b39ff4d6787bad3001c54a",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 81f5f46..8329c77 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1,2 +1 @@",
+ "-x.someProperty;",
+ " x.someOtherProperty"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "07ebf2e9216478041a23449ff3aa79e25dd6a5da"
+ "shas": "38ee25545f8644cee42edb45ef2f7b29b26892d5..6188b94ce3872e80b40738d01c4853a467d502c2"
}
,{
"testCaseDescription": "javascript-member-access-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"member-access.js"
],
- "sha1": "07ebf2e9216478041a23449ff3aa79e25dd6a5da",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 8329c77..e69de29 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1 +0,0 @@",
+ "-x.someOtherProperty"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3703258beda4cec843b8f1d61576e214ffd3651b"
+ "shas": "6188b94ce3872e80b40738d01c4853a467d502c2..bcba202e709aea072f614c126e2a5bb356cbf3fe"
}]
diff --git a/test/corpus/diff-summaries/javascript/method-call.json b/test/corpus/diff-summaries/javascript/method-call.json
index f986bfc05..847d35bae 100644
--- a/test/corpus/diff-summaries/javascript/method-call.json
+++ b/test/corpus/diff-summaries/javascript/method-call.json
@@ -25,9 +25,16 @@
"filePaths": [
"method-call.js"
],
- "sha1": "3a19dee8da1e0544c2cf975d850a6ce707912b35",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index e69de29..07ab90c 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -0,0 +1 @@",
+ "+object.someMethod(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d65701648386aeedc450735d2d231ad241b0e62e"
+ "shas": "f8662860eb083b9e95b5cc1c706a7872a4779532..616ca3e3b4a298f69107bd17d20b8fe2e5fd3d80"
}
,{
"testCaseDescription": "javascript-method-call-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"method-call.js"
],
- "sha1": "d65701648386aeedc450735d2d231ad241b0e62e",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index 07ab90c..9341e17 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1 +1,3 @@",
+ "+object.someMethod(arg1, \"arg3\");",
+ "+object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "66cc70211c2edf4ff6090e439a410da10a6ffb8f"
+ "shas": "616ca3e3b4a298f69107bd17d20b8fe2e5fd3d80..1ddf2d53694021927a1783fc78ab68dca0508ce9"
}
,{
"testCaseDescription": "javascript-method-call-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"method-call.js"
],
- "sha1": "66cc70211c2edf4ff6090e439a410da10a6ffb8f",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index 9341e17..f6ada2d 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-object.someMethod(arg1, \"arg3\");",
+ "+object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "42b4144cde71d8c7afc757f4881794449cdf0fc5"
+ "shas": "1ddf2d53694021927a1783fc78ab68dca0508ce9..741134e42738870aeb25a8395d4a656ddd86bf4b"
}
,{
"testCaseDescription": "javascript-method-call-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"method-call.js"
],
- "sha1": "42b4144cde71d8c7afc757f4881794449cdf0fc5",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index f6ada2d..9341e17 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-object.someMethod(arg1, \"arg2\");",
+ "+object.someMethod(arg1, \"arg3\");",
+ " object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fcd77d257692d8e35ec4ab1b7b308f9701f6021c"
+ "shas": "741134e42738870aeb25a8395d4a656ddd86bf4b..4778b03d41ac4397158cf93d091d520be85bfc34"
}
,{
"testCaseDescription": "javascript-method-call-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"method-call.js"
],
- "sha1": "fcd77d257692d8e35ec4ab1b7b308f9701f6021c",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index 9341e17..894dcf6 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1,3 +1,2 @@",
+ "-object.someMethod(arg1, \"arg3\");",
+ "-object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg2\");",
+ "+object.someMethod(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c0ee844e49724d0ecebc7320ff9753669ded229b"
+ "shas": "4778b03d41ac4397158cf93d091d520be85bfc34..b2b8e482425d3459e6e1cab14dd7c6201bfa516e"
}
,{
"testCaseDescription": "javascript-method-call-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"method-call.js"
],
- "sha1": "c0ee844e49724d0ecebc7320ff9753669ded229b",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index 894dcf6..a82528c 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1,2 +1 @@",
+ "-object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "297e775c0aa3afe5cca15accc9b466c2f095ea56"
+ "shas": "b2b8e482425d3459e6e1cab14dd7c6201bfa516e..54e0a5e18b235909c85caf03159b380559d9c68d"
}
,{
"testCaseDescription": "javascript-method-call-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"method-call.js"
],
- "sha1": "297e775c0aa3afe5cca15accc9b466c2f095ea56",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index a82528c..e69de29 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1 +0,0 @@",
+ "-object.someMethod(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6087206d2569a100e711f522134188e6f4477aec"
+ "shas": "54e0a5e18b235909c85caf03159b380559d9c68d..5d5d40b2fa515dfcb7494d9b83f22687c56de0f5"
}]
diff --git a/test/corpus/diff-summaries/javascript/named-function.json b/test/corpus/diff-summaries/javascript/named-function.json
index 1f5b6c444..03ecda93a 100644
--- a/test/corpus/diff-summaries/javascript/named-function.json
+++ b/test/corpus/diff-summaries/javascript/named-function.json
@@ -25,9 +25,16 @@
"filePaths": [
"named-function.js"
],
- "sha1": "437d13155925d96902bc67c5d88d607d97762adf",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index e69de29..94b19f8 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -0,0 +1 @@",
+ "+function myFunction(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6cd566b50dac1a965d30e07f4df3cfb6a5b82ceb"
+ "shas": "973cce7b94116a9e6e8b399f9f0a50bd107fb9b5..0af41b91893fcc8e9172616a4e5a71c70ee47985"
}
,{
"testCaseDescription": "javascript-named-function-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"named-function.js"
],
- "sha1": "6cd566b50dac1a965d30e07f4df3cfb6a5b82ceb",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index 94b19f8..cb766a0 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1 +1,3 @@",
+ "+function anotherFunction() { return false; };",
+ "+function myFunction(arg1, arg2) { arg2; };",
+ " function myFunction(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7a7e01292865470514c072bb9c4f104c27c45f78"
+ "shas": "0af41b91893fcc8e9172616a4e5a71c70ee47985..2fe69bd38fe1db507331dc14063479b66eb2a880"
}
,{
"testCaseDescription": "javascript-named-function-delete-insert-test",
@@ -174,9 +190,19 @@
"filePaths": [
"named-function.js"
],
- "sha1": "7a7e01292865470514c072bb9c4f104c27c45f78",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index cb766a0..c9cff07 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function anotherFunction() { return false; };",
+ "+function myFunction(arg1, arg2) { arg2; };",
+ " function myFunction(arg1, arg2) { arg2; };",
+ " function myFunction(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0dcb7d069e3c25a64997ec5a0aae69c7326c3afd"
+ "shas": "2fe69bd38fe1db507331dc14063479b66eb2a880..4b0a0bcf80003eb74b67b8947f8a0443cb2ad80f"
}
,{
"testCaseDescription": "javascript-named-function-replacement-test",
@@ -277,9 +303,19 @@
"filePaths": [
"named-function.js"
],
- "sha1": "0dcb7d069e3c25a64997ec5a0aae69c7326c3afd",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index c9cff07..cb766a0 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function myFunction(arg1, arg2) { arg2; };",
+ "+function anotherFunction() { return false; };",
+ " function myFunction(arg1, arg2) { arg2; };",
+ " function myFunction(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1cb329c5a156713abab6084c18234ca7d7344b45"
+ "shas": "4b0a0bcf80003eb74b67b8947f8a0443cb2ad80f..785a621c11eb5f6e1e93d2ea1e40828c8786ae2d"
}
,{
"testCaseDescription": "javascript-named-function-delete-replacement-test",
@@ -338,9 +374,19 @@
"filePaths": [
"named-function.js"
],
- "sha1": "1cb329c5a156713abab6084c18234ca7d7344b45",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index cb766a0..148bcc7 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function anotherFunction() { return false; };",
+ "-function myFunction(arg1, arg2) { arg2; };",
+ " function myFunction(arg1, arg2) { arg2; };",
+ "+function anotherFunction() { return false; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a1a233d56416a2ca9c51276a1c9f05a6540037c3"
+ "shas": "785a621c11eb5f6e1e93d2ea1e40828c8786ae2d..7ecdd3334fd0090f017044bd0780b5a5df128eda"
}
,{
"testCaseDescription": "javascript-named-function-delete-test",
@@ -369,9 +415,17 @@
"filePaths": [
"named-function.js"
],
- "sha1": "a1a233d56416a2ca9c51276a1c9f05a6540037c3",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index 148bcc7..80e11b0 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1,2 +1 @@",
+ "-function myFunction(arg1, arg2) { arg2; };",
+ " function anotherFunction() { return false; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5cd383e1c4c3e1e1177a5242f5815e9a4078d8bc"
+ "shas": "7ecdd3334fd0090f017044bd0780b5a5df128eda..92cb451c62ab6f9a63bad5a24b21beb2cbe9bdde"
}
,{
"testCaseDescription": "javascript-named-function-delete-rest-test",
@@ -400,7 +454,14 @@
"filePaths": [
"named-function.js"
],
- "sha1": "5cd383e1c4c3e1e1177a5242f5815e9a4078d8bc",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index 80e11b0..e69de29 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1 +0,0 @@",
+ "-function anotherFunction() { return false; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "00c3afcb0bf345232b8117cd6726492a096d4c5a"
+ "shas": "92cb451c62ab6f9a63bad5a24b21beb2cbe9bdde..0cbc55e481f01ab536c7832c5ebbc21d7f9e9021"
}]
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 bcc2b1718..a0aa38dcc 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
@@ -25,9 +25,16 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "e01da1d7da05b823873a3d54668f908216c92694",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index e69de29..d205614 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -0,0 +1 @@",
+ "+function f(arg1, arg2) { do { something(arg1); } while (arg2); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c40a8da30fd77e505774c5124454d46f5e07f608"
+ "shas": "b916dd0d4e57f46f672acd9dc9130eef9e0bcc60..b60cbbceaf5939517572a1c7ebc7fd80db858b96"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "c40a8da30fd77e505774c5124454d46f5e07f608",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index d205614..5dfcca6 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1 +1,3 @@",
+ "+function f(arg1, arg2) { do { something(arg2); } while (arg1); }",
+ "+function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8d1f422c1d1af152ae1d8ed0fa4391ac6ec6f1e6"
+ "shas": "b60cbbceaf5939517572a1c7ebc7fd80db858b96..3da97953dcda4f775d102a777c46bf8476ac6ee6"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-insert-test",
@@ -141,9 +157,19 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "8d1f422c1d1af152ae1d8ed0fa4391ac6ec6f1e6",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index 5dfcca6..49cff7e 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function f(arg1, arg2) { do { something(arg2); } while (arg1); }",
+ "+function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e04397861769262f0c682e6ac4050be04302616c"
+ "shas": "3da97953dcda4f775d102a777c46bf8476ac6ee6..d91742e7e9daa195667f006f6eb20e19c6f16c00"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-replacement-test",
@@ -211,9 +237,19 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "e04397861769262f0c682e6ac4050be04302616c",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index 49cff7e..5dfcca6 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ "+function f(arg1, arg2) { do { something(arg2); } while (arg1); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "da3be5ae932bfa8baf3d88de70ba76dc3503a756"
+ "shas": "d91742e7e9daa195667f006f6eb20e19c6f16c00..f4842813b2ac2a5996ad23bbeeb6d022a3c29f8e"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-replacement-test",
@@ -272,9 +308,19 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "da3be5ae932bfa8baf3d88de70ba76dc3503a756",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index 5dfcca6..babb1e6 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function f(arg1, arg2) { do { something(arg2); } while (arg1); }",
+ "-function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ "+function f(arg1, arg2) { do { something(arg2); } while (arg1); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8b1f6a80d4434515e3129552987804e58ee95182"
+ "shas": "f4842813b2ac2a5996ad23bbeeb6d022a3c29f8e..39c63fc4aa834c62a569d089f3c660ff87519271"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-test",
@@ -303,9 +349,17 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "8b1f6a80d4434515e3129552987804e58ee95182",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index babb1e6..2b15580 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1,2 +1 @@",
+ "-function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg2); } while (arg1); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "78e6515b27f094beeb4b3b6dec2bbe60bb57a088"
+ "shas": "39c63fc4aa834c62a569d089f3c660ff87519271..6cdad31d7f48683bfe6ff831cd286c79d2467e8f"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-rest-test",
@@ -334,7 +388,14 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "78e6515b27f094beeb4b3b6dec2bbe60bb57a088",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index 2b15580..e69de29 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1 +0,0 @@",
+ "-function f(arg1, arg2) { do { something(arg2); } while (arg1); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1011ea99d2c513437073a38030c1290fcc06cac4"
+ "shas": "6cdad31d7f48683bfe6ff831cd286c79d2467e8f..94d7e0ef831c81697b130d8e7c032b876c270e33"
}]
diff --git a/test/corpus/diff-summaries/javascript/nested-functions.json b/test/corpus/diff-summaries/javascript/nested-functions.json
index e26074ef7..3fecd1805 100644
--- a/test/corpus/diff-summaries/javascript/nested-functions.json
+++ b/test/corpus/diff-summaries/javascript/nested-functions.json
@@ -25,9 +25,16 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "d2246a50ed33ef4c748bfdaf80bbf4eb41cc6c57",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index e69de29..72531d8 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -0,0 +1 @@",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "63ff6752030c14e33484d0d26272a4de396b237d"
+ "shas": "d1b2bee18a7da4fefa2a4786b2f692fc5795f48c..71dc5237f7ffca394739d3f93487a7187b0a12a8"
}
,{
"testCaseDescription": "javascript-nested-functions-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "63ff6752030c14e33484d0d26272a4de396b237d",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index 72531d8..c960aae 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1 +1,3 @@",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d4d0acb878a952ab891609248be8ca565048582e"
+ "shas": "71dc5237f7ffca394739d3f93487a7187b0a12a8..7e5b3b060a63fde4ac14ad0902c3cfa453e7342e"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-insert-test",
@@ -141,9 +157,19 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "d4d0acb878a952ab891609248be8ca565048582e",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index c960aae..1b9b61a 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1,3 +1,3 @@",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c834e67b0218be43f52524993748a6eef26556cc"
+ "shas": "7e5b3b060a63fde4ac14ad0902c3cfa453e7342e..ca415e38a948a4c4de9d07e37c1c9cfc34d8445c"
}
,{
"testCaseDescription": "javascript-nested-functions-replacement-test",
@@ -211,9 +237,19 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "c834e67b0218be43f52524993748a6eef26556cc",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index 1b9b61a..c960aae 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1,3 +1,3 @@",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "85df5ab1b8a75302dfa8dcafc32613bc6062fc6f"
+ "shas": "ca415e38a948a4c4de9d07e37c1c9cfc34d8445c..2c630214d8f19ee0f2818b939a13a27d703d2b17"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-replacement-test",
@@ -272,9 +308,19 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "85df5ab1b8a75302dfa8dcafc32613bc6062fc6f",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index c960aae..81522c7 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1,3 +1,2 @@",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d0f03610458a0d43ff3d131dd2ac8b7cd00b6d39"
+ "shas": "2c630214d8f19ee0f2818b939a13a27d703d2b17..8d2f83fd46bff59083e96ad5e3f2840603171027"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-test",
@@ -303,9 +349,17 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "d0f03610458a0d43ff3d131dd2ac8b7cd00b6d39",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index 81522c7..3056480 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1,2 +1 @@",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "db08f5d444e81130894b841385b1aded9720a6f5"
+ "shas": "8d2f83fd46bff59083e96ad5e3f2840603171027..13f268f35a3fde68001653b29f9e0eb0568c4d14"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-rest-test",
@@ -334,7 +388,14 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "db08f5d444e81130894b841385b1aded9720a6f5",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index 3056480..e69de29 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1 +0,0 @@",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e01da1d7da05b823873a3d54668f908216c92694"
+ "shas": "13f268f35a3fde68001653b29f9e0eb0568c4d14..b916dd0d4e57f46f672acd9dc9130eef9e0bcc60"
}]
diff --git a/test/corpus/diff-summaries/javascript/null.json b/test/corpus/diff-summaries/javascript/null.json
index 279b95dee..9a5c8f7fd 100644
--- a/test/corpus/diff-summaries/javascript/null.json
+++ b/test/corpus/diff-summaries/javascript/null.json
@@ -25,9 +25,16 @@
"filePaths": [
"null.js"
],
- "sha1": "6d600208cc985a6c0fbbbdbd54227f1010a9bb14",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index e69de29..ff464d1 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -0,0 +1 @@",
+ "+null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9b71ef1c47d67951f4ecc3dae50e424cbfecb573"
+ "shas": "655d7887b70794042aa3e0f4d6ea174c1b32af1c..f25bb82f823a669a0b6a9c19160ba03ab21d318b"
}
,{
"testCaseDescription": "javascript-null-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"null.js"
],
- "sha1": "9b71ef1c47d67951f4ecc3dae50e424cbfecb573",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index ff464d1..2d3c3e0 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1 +1,3 @@",
+ "+return null;",
+ "+null;",
+ " null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8c527baf4dee64ca32e1c4afe79297c797b1d388"
+ "shas": "f25bb82f823a669a0b6a9c19160ba03ab21d318b..4669bb697216411b02390ac038c699f1db9d76ee"
}
,{
"testCaseDescription": "javascript-null-delete-insert-test",
@@ -117,9 +133,19 @@
"filePaths": [
"null.js"
],
- "sha1": "8c527baf4dee64ca32e1c4afe79297c797b1d388",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index 2d3c3e0..3122897 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1,3 +1,3 @@",
+ "-return null;",
+ "+null;",
+ " null;",
+ " null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "48099f6976342322c2143c1f57201c85a7ddb9e7"
+ "shas": "4669bb697216411b02390ac038c699f1db9d76ee..ff3a8cc7449b04b7a15a6ab31ea1f5e78283db3e"
}
,{
"testCaseDescription": "javascript-null-replacement-test",
@@ -163,9 +189,19 @@
"filePaths": [
"null.js"
],
- "sha1": "48099f6976342322c2143c1f57201c85a7ddb9e7",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index 3122897..2d3c3e0 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1,3 +1,3 @@",
+ "-null;",
+ "+return null;",
+ " null;",
+ " null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4be96fd5ce010d81a8cca69132893d977c967ceb"
+ "shas": "ff3a8cc7449b04b7a15a6ab31ea1f5e78283db3e..0e96cfb0a6c4746ef4911d99134eebcac36edbd8"
}
,{
"testCaseDescription": "javascript-null-delete-replacement-test",
@@ -224,9 +260,19 @@
"filePaths": [
"null.js"
],
- "sha1": "4be96fd5ce010d81a8cca69132893d977c967ceb",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index 2d3c3e0..0eb99c8 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1,3 +1,2 @@",
+ "-return null;",
+ "-null;",
+ " null;",
+ "+return null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d0b15cb05c48d6748b7b3c37c51a41f321564feb"
+ "shas": "0e96cfb0a6c4746ef4911d99134eebcac36edbd8..88958970d3cca5d0413e83a7ff37f1092d0d9299"
}
,{
"testCaseDescription": "javascript-null-delete-test",
@@ -255,9 +301,17 @@
"filePaths": [
"null.js"
],
- "sha1": "d0b15cb05c48d6748b7b3c37c51a41f321564feb",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index 0eb99c8..76137ff 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1,2 +1 @@",
+ "-null;",
+ " return null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4cd110586313e3903a866bd42d181a02c05cc693"
+ "shas": "88958970d3cca5d0413e83a7ff37f1092d0d9299..b5db27b021a3c11c985a28653aca15041f140fec"
}
,{
"testCaseDescription": "javascript-null-delete-rest-test",
@@ -286,7 +340,14 @@
"filePaths": [
"null.js"
],
- "sha1": "4cd110586313e3903a866bd42d181a02c05cc693",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index 76137ff..e69de29 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1 +0,0 @@",
+ "-return null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ed321b51c08d6640a37c2c75423bda8952ed1a3a"
+ "shas": "b5db27b021a3c11c985a28653aca15041f140fec..9f36bd70533d2f145bb9661791f0ea760bf949d5"
}]
diff --git a/test/corpus/diff-summaries/javascript/number.json b/test/corpus/diff-summaries/javascript/number.json
index a5c110203..4e8d7ac06 100644
--- a/test/corpus/diff-summaries/javascript/number.json
+++ b/test/corpus/diff-summaries/javascript/number.json
@@ -25,9 +25,16 @@
"filePaths": [
"number.js"
],
- "sha1": "616022d16e903375ee8cb705926e3130e700baa1",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index e69de29..398050c 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -0,0 +1 @@",
+ "+101"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5d899482e4a1b162833c0beff2017cd5f954d9af"
+ "shas": "aa6143f1a8ae9ca9b1ee3577121858208df3cce0..3838259f90e9c1e4e6ce33e99b8d9a0fbcd9e616"
}
,{
"testCaseDescription": "javascript-number-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"number.js"
],
- "sha1": "5d899482e4a1b162833c0beff2017cd5f954d9af",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index 398050c..16da476 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1 +1,3 @@",
+ "+102",
+ "+101",
+ " 101"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fb905efd1a20da0aa16df3079a05d5a0d2cdf4df"
+ "shas": "3838259f90e9c1e4e6ce33e99b8d9a0fbcd9e616..6e18d86d44c74acdcea5dc6ea75a8169152e0dd2"
}
,{
"testCaseDescription": "javascript-number-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"number.js"
],
- "sha1": "fb905efd1a20da0aa16df3079a05d5a0d2cdf4df",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index 16da476..252b3e8 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1,3 +1,3 @@",
+ "-102",
+ "+101",
+ " 101",
+ " 101"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5ec23b61593f8f846be54c2626003199f8ba8f31"
+ "shas": "6e18d86d44c74acdcea5dc6ea75a8169152e0dd2..b40e32fd74e885cdf5d9617ef37150ec3d414177"
}
,{
"testCaseDescription": "javascript-number-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"number.js"
],
- "sha1": "5ec23b61593f8f846be54c2626003199f8ba8f31",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index 252b3e8..16da476 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1,3 +1,3 @@",
+ "-101",
+ "+102",
+ " 101",
+ " 101"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "352335d1de8f6aa743824442906f595f413cf3a9"
+ "shas": "b40e32fd74e885cdf5d9617ef37150ec3d414177..85a591e8bebf6a7b8b9adfdebebfb4b8776ab809"
}
,{
"testCaseDescription": "javascript-number-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"number.js"
],
- "sha1": "352335d1de8f6aa743824442906f595f413cf3a9",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index 16da476..bb77dfb 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1,3 +1,2 @@",
+ "-102",
+ "-101",
+ " 101",
+ "+102"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a4653469e371e09fd2e5dd000025dd361d9a8b4b"
+ "shas": "85a591e8bebf6a7b8b9adfdebebfb4b8776ab809..3e5ee4738617f0b4536cee654c79c7c71e8d7e7b"
}
,{
"testCaseDescription": "javascript-number-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"number.js"
],
- "sha1": "a4653469e371e09fd2e5dd000025dd361d9a8b4b",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index bb77dfb..257e563 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1,2 +1 @@",
+ "-101",
+ " 102"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3327da820137920926a11e97959cad0e88da996f"
+ "shas": "3e5ee4738617f0b4536cee654c79c7c71e8d7e7b..15bf3e42bb84c62933b0d29e0b675bca24cc66b2"
}
,{
"testCaseDescription": "javascript-number-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"number.js"
],
- "sha1": "3327da820137920926a11e97959cad0e88da996f",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index 257e563..e69de29 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1 +0,0 @@",
+ "-102"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e3169a584f82eaedeb405338ea6175466369ab58"
+ "shas": "15bf3e42bb84c62933b0d29e0b675bca24cc66b2..2e348ee88f62c0857d6f6ce2ab3ee0d46f12afeb"
}]
diff --git a/test/corpus/diff-summaries/javascript/object.json b/test/corpus/diff-summaries/javascript/object.json
index 123b0ed14..c5bdff968 100644
--- a/test/corpus/diff-summaries/javascript/object.json
+++ b/test/corpus/diff-summaries/javascript/object.json
@@ -25,9 +25,16 @@
"filePaths": [
"object.js"
],
- "sha1": "00efe14aec8ad3006518ee149f738adee0aeba5d",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index e69de29..fe17bb2 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -0,0 +1 @@",
+ "+{ \"key1\": \"value1\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9503250634810e806419552ad9ad18891bbc219e"
+ "shas": "aaba67c460efdf59f04a498c4699fcb690d9b490..7faf2acf9f69d7f3b03dde0d6a5e1d2f65871d01"
}
,{
"testCaseDescription": "javascript-object-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"object.js"
],
- "sha1": "9503250634810e806419552ad9ad18891bbc219e",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index fe17bb2..741c3dc 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1 +1,3 @@",
+ "+{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };",
+ "+{ \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6f5f810bf7512233cd31d12a0324e3fee4a476d2"
+ "shas": "7faf2acf9f69d7f3b03dde0d6a5e1d2f65871d01..0b2c6e3141cb23beeb872694d5f1587716ac4040"
}
,{
"testCaseDescription": "javascript-object-delete-insert-test",
@@ -117,9 +133,19 @@
"filePaths": [
"object.js"
],
- "sha1": "6f5f810bf7512233cd31d12a0324e3fee4a476d2",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index 741c3dc..701239d 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1,3 +1,3 @@",
+ "-{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };",
+ "+{ \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b4c00c718fe8766bce38b8c8bb263a6a24b4f29e"
+ "shas": "0b2c6e3141cb23beeb872694d5f1587716ac4040..fd282261939913a45699187bcebd1df33dd8f354"
}
,{
"testCaseDescription": "javascript-object-replacement-test",
@@ -163,9 +189,19 @@
"filePaths": [
"object.js"
],
- "sha1": "b4c00c718fe8766bce38b8c8bb263a6a24b4f29e",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index 701239d..741c3dc 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1,3 +1,3 @@",
+ "-{ \"key1\": \"value1\" };",
+ "+{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };",
+ " { \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9a21cddbf2e326d66db1d30048a505c7b4114a17"
+ "shas": "fd282261939913a45699187bcebd1df33dd8f354..cf63812f1b4711a1dff84db2df97b987df9cfb6d"
}
,{
"testCaseDescription": "javascript-object-delete-replacement-test",
@@ -224,9 +260,19 @@
"filePaths": [
"object.js"
],
- "sha1": "9a21cddbf2e326d66db1d30048a505c7b4114a17",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index 741c3dc..9e48273 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1,3 +1,2 @@",
+ "-{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };",
+ "-{ \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\" };",
+ "+{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c67dbc109159cb73130a14bff8efb22969fa3e7d"
+ "shas": "cf63812f1b4711a1dff84db2df97b987df9cfb6d..1b3cdfbad081f4c455fa9534d9cba4547f5ab6f1"
}
,{
"testCaseDescription": "javascript-object-delete-test",
@@ -255,9 +301,17 @@
"filePaths": [
"object.js"
],
- "sha1": "c67dbc109159cb73130a14bff8efb22969fa3e7d",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index 9e48273..12d063a 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1,2 +1 @@",
+ "-{ \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "575cfe90651d66ddda91b0764d9107f1718c1bfb"
+ "shas": "1b3cdfbad081f4c455fa9534d9cba4547f5ab6f1..607a72ed7ff28c76667ef67aca1472e2aa4be099"
}
,{
"testCaseDescription": "javascript-object-delete-rest-test",
@@ -286,7 +340,14 @@
"filePaths": [
"object.js"
],
- "sha1": "575cfe90651d66ddda91b0764d9107f1718c1bfb",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index 12d063a..e69de29 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1 +0,0 @@",
+ "-{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c3ba4a1505773022c8c9750803b2f78c821f80a1"
+ "shas": "607a72ed7ff28c76667ef67aca1472e2aa4be099..5f4dfa791577127cebc7f5fa8c7d94b7427980f3"
}]
diff --git a/test/corpus/diff-summaries/javascript/objects-with-methods.json b/test/corpus/diff-summaries/javascript/objects-with-methods.json
index 88930a7c3..33feda07d 100644
--- a/test/corpus/diff-summaries/javascript/objects-with-methods.json
+++ b/test/corpus/diff-summaries/javascript/objects-with-methods.json
@@ -16,7 +16,7 @@
]
}
},
- "summary": "Added the '{ add }' object"
+ "summary": "Added the '{ add(a, b) }' object"
}
]
},
@@ -25,9 +25,16 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "8662f58f1d7ce21fddcefecae990742a5d1398dc",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index e69de29..7421e18 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -0,0 +1 @@",
+ "+{ add(a, b) { return a + b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b591df548ffb5ef563a30246d6492b39fb69a564"
+ "shas": "e66b1b20abc596d2b560eaa80f1749c79816f9ff..d3b8c609f29da1978a60c14da5d0ca5dfc565eff"
}
,{
"testCaseDescription": "javascript-objects-with-methods-replacement-insert-test",
@@ -47,7 +54,7 @@
]
}
},
- "summary": "Added the '{ subtract }' object"
+ "summary": "Added the '{ subtract(a, b) }' object"
},
{
"span": {
@@ -62,7 +69,7 @@
]
}
},
- "summary": "Added the '{ add }' object"
+ "summary": "Added the '{ add(a, b) }' object"
}
]
},
@@ -71,9 +78,18 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "b591df548ffb5ef563a30246d6492b39fb69a564",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 7421e18..59eb3a3 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1 +1,3 @@",
+ "+{ subtract(a, b) { return a - b; } };",
+ "+{ add(a, b) { return a + b; } };",
+ " { add(a, b) { return a + b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ee23a64bc6c8edd4994205c77bf77a35bcb40493"
+ "shas": "d3b8c609f29da1978a60c14da5d0ca5dfc565eff..71f9fe548526a54588efe8ccf43fb16946dde439"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-insert-test",
@@ -105,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'subtract' identifier with the 'add' identifier in the add method"
+ "summary": "Replaced the 'subtract' identifier with the 'add' identifier in the 'add(a, b)' method"
}
]
},
@@ -114,9 +130,19 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "ee23a64bc6c8edd4994205c77bf77a35bcb40493",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 59eb3a3..05689b1 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1,3 +1,3 @@",
+ "-{ subtract(a, b) { return a - b; } };",
+ "+{ add(a, b) { return a + b; } };",
+ " { add(a, b) { return a + b; } };",
+ " { add(a, b) { return a + b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5afe59e01be0dfa586cf09188b26b97960e84b71"
+ "shas": "71f9fe548526a54588efe8ccf43fb16946dde439..3651aee8e277793117960f9223391b0cfdb1f814"
}
,{
"testCaseDescription": "javascript-objects-with-methods-replacement-test",
@@ -148,7 +174,7 @@
}
]
},
- "summary": "Replaced the 'add' identifier with the 'subtract' identifier in the subtract method"
+ "summary": "Replaced the 'add' identifier with the 'subtract' identifier in the 'subtract(a, b)' method"
}
]
},
@@ -157,9 +183,19 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "5afe59e01be0dfa586cf09188b26b97960e84b71",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 05689b1..59eb3a3 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1,3 +1,3 @@",
+ "-{ add(a, b) { return a + b; } };",
+ "+{ subtract(a, b) { return a - b; } };",
+ " { add(a, b) { return a + b; } };",
+ " { add(a, b) { return a + b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3723264ddcbd5d252f20a04e13f2813874ea7a75"
+ "shas": "3651aee8e277793117960f9223391b0cfdb1f814..af0586db52b5b97c1c819ee5e107835fa2299249"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-replacement-test",
@@ -179,7 +215,7 @@
]
}
},
- "summary": "Deleted the '{ subtract }' object"
+ "summary": "Deleted the '{ subtract(a, b) }' object"
},
{
"span": {
@@ -194,7 +230,7 @@
]
}
},
- "summary": "Deleted the '{ add }' object"
+ "summary": "Deleted the '{ add(a, b) }' object"
},
{
"span": {
@@ -209,7 +245,7 @@
]
}
},
- "summary": "Added the '{ subtract }' object"
+ "summary": "Added the '{ subtract(a, b) }' object"
}
]
},
@@ -218,9 +254,19 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "3723264ddcbd5d252f20a04e13f2813874ea7a75",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 59eb3a3..29d3998 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1,3 +1,2 @@",
+ "-{ subtract(a, b) { return a - b; } };",
+ "-{ add(a, b) { return a + b; } };",
+ " { add(a, b) { return a + b; } };",
+ "+{ subtract(a, b) { return a - b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f2e3bfb506337dbb81c078e49bfca3c4d72abefa"
+ "shas": "af0586db52b5b97c1c819ee5e107835fa2299249..a1ef0cba5455912ff148f7bf8afbc74061d8de10"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-test",
@@ -240,7 +286,7 @@
]
}
},
- "summary": "Deleted the '{ add }' object"
+ "summary": "Deleted the '{ add(a, b) }' object"
}
]
},
@@ -249,9 +295,17 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "f2e3bfb506337dbb81c078e49bfca3c4d72abefa",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 29d3998..80ad7f0 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1,2 +1 @@",
+ "-{ add(a, b) { return a + b; } };",
+ " { subtract(a, b) { return a - b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "59aab91326ae0dbd9332b64ea11a42f940b4437f"
+ "shas": "a1ef0cba5455912ff148f7bf8afbc74061d8de10..896cd9fdc71791d876ea5108de8b34631f284c5a"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-rest-test",
@@ -271,7 +325,7 @@
]
}
},
- "summary": "Deleted the '{ subtract }' object"
+ "summary": "Deleted the '{ subtract(a, b) }' object"
}
]
},
@@ -280,7 +334,14 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "59aab91326ae0dbd9332b64ea11a42f940b4437f",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 80ad7f0..e69de29 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1 +0,0 @@",
+ "-{ subtract(a, b) { return a - b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ee6b3d5d274912c071eadd10cb5bea9b96b30cb8"
+ "shas": "896cd9fdc71791d876ea5108de8b34631f284c5a..c1ec2fd690eae01418882f3dbba8b6a5c0c3c2eb"
}]
diff --git a/test/corpus/diff-summaries/javascript/regex.json b/test/corpus/diff-summaries/javascript/regex.json
index 076619ede..d7c178a87 100644
--- a/test/corpus/diff-summaries/javascript/regex.json
+++ b/test/corpus/diff-summaries/javascript/regex.json
@@ -25,9 +25,16 @@
"filePaths": [
"regex.js"
],
- "sha1": "97a7c83a9e020ac198c1fbf23d38b3089f4484b1",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index e69de29..b381842 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -0,0 +1 @@",
+ "+/one/g;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7f8c1785dae66151e5dd0a4d623d23aba69ee46b"
+ "shas": "734bede3c6c3771f011aa729a417011d310ec5cc..9dbffbb28707342ebcd361c29b0d670a271ddb04"
}
,{
"testCaseDescription": "javascript-regex-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"regex.js"
],
- "sha1": "7f8c1785dae66151e5dd0a4d623d23aba69ee46b",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index b381842..6ed4b42 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1 +1,3 @@",
+ "+/on[^/]afe/gim;",
+ "+/one/g;",
+ " /one/g;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c983dec6883ab781783d20943e8751acca12e517"
+ "shas": "9dbffbb28707342ebcd361c29b0d670a271ddb04..f294c4a4aac8d0a945272edb200af0866b0d5a0f"
}
,{
"testCaseDescription": "javascript-regex-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"regex.js"
],
- "sha1": "c983dec6883ab781783d20943e8751acca12e517",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index 6ed4b42..abb87ec 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1,3 +1,3 @@",
+ "-/on[^/]afe/gim;",
+ "+/one/g;",
+ " /one/g;",
+ " /one/g;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7afab11946dbc25be5a0bd44395e35c43a52dce5"
+ "shas": "f294c4a4aac8d0a945272edb200af0866b0d5a0f..c158c5219c063572ee6664525f8fb4377178cdc3"
}
,{
"testCaseDescription": "javascript-regex-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"regex.js"
],
- "sha1": "7afab11946dbc25be5a0bd44395e35c43a52dce5",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index abb87ec..6ed4b42 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1,3 +1,3 @@",
+ "-/one/g;",
+ "+/on[^/]afe/gim;",
+ " /one/g;",
+ " /one/g;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "555b1cad7a4da4e9a9efe0c97f6a1896e4e16aa2"
+ "shas": "c158c5219c063572ee6664525f8fb4377178cdc3..38ad972ed8f499cb320e4584c4ae1b95d4e70f41"
}
,{
"testCaseDescription": "javascript-regex-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"regex.js"
],
- "sha1": "555b1cad7a4da4e9a9efe0c97f6a1896e4e16aa2",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index 6ed4b42..9f57e91 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1,3 +1,2 @@",
+ "-/on[^/]afe/gim;",
+ "-/one/g;",
+ " /one/g;",
+ "+/on[^/]afe/gim;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "035f601809f5818ed358b56e52e2d3888b51de9a"
+ "shas": "38ad972ed8f499cb320e4584c4ae1b95d4e70f41..79078d16f7a00fca2b3dbf3cf7dadd8f5ba7929c"
}
,{
"testCaseDescription": "javascript-regex-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"regex.js"
],
- "sha1": "035f601809f5818ed358b56e52e2d3888b51de9a",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index 9f57e91..9b04194 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1,2 +1 @@",
+ "-/one/g;",
+ " /on[^/]afe/gim;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "725dc154b47967e008f928e59eb777bab1a08d59"
+ "shas": "79078d16f7a00fca2b3dbf3cf7dadd8f5ba7929c..f293398786080c6f5b99e7c36ba482702f5cbbae"
}
,{
"testCaseDescription": "javascript-regex-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"regex.js"
],
- "sha1": "725dc154b47967e008f928e59eb777bab1a08d59",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index 9b04194..e69de29 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1 +0,0 @@",
+ "-/on[^/]afe/gim;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "dc9aa0f5ce2176319c7eb9475db8787876afb4d9"
+ "shas": "f293398786080c6f5b99e7c36ba482702f5cbbae..4951403c16600a8ebe50779236bcbc480c823807"
}]
diff --git a/test/corpus/diff-summaries/javascript/relational-operator.json b/test/corpus/diff-summaries/javascript/relational-operator.json
index a51f249ac..51e9d2e7e 100644
--- a/test/corpus/diff-summaries/javascript/relational-operator.json
+++ b/test/corpus/diff-summaries/javascript/relational-operator.json
@@ -25,9 +25,16 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "149d0a9500261cd37b696c4ab2527d34f0133522",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index e69de29..4021910 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -0,0 +1 @@",
+ "+x < y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "44342fbcc55ee68fc6f6bda399b68114faf72cee"
+ "shas": "4e47562dd59646a6c6c55ab138660495394bc5c9..58bdba5f1c185ad7ae6f4275533f799aa25e9020"
}
,{
"testCaseDescription": "javascript-relational-operator-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "44342fbcc55ee68fc6f6bda399b68114faf72cee",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index 4021910..dbef050 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1 +1,3 @@",
+ "+x <= y;",
+ "+x < y;",
+ " x < y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "429580bbd2a8e6ab94ac812f9efe401ce53507c7"
+ "shas": "58bdba5f1c185ad7ae6f4275533f799aa25e9020..440204afe68655c97580bc91b578d9f4a0475c6c"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-insert-test",
@@ -84,9 +100,19 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "429580bbd2a8e6ab94ac812f9efe401ce53507c7",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index dbef050..a9ff7f6 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-x <= y;",
+ "+x < y;",
+ " x < y;",
+ " x < y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7f27cfcac5d2c7b7bd1708c242942a35aa932f16"
+ "shas": "440204afe68655c97580bc91b578d9f4a0475c6c..903fdf57bcf14cae9e043c4fbafb911715076dda"
}
,{
"testCaseDescription": "javascript-relational-operator-replacement-test",
@@ -97,9 +123,19 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "7f27cfcac5d2c7b7bd1708c242942a35aa932f16",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index a9ff7f6..dbef050 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-x < y;",
+ "+x <= y;",
+ " x < y;",
+ " x < y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b2de8add90f64f679d620edb09f78d9ef7b77619"
+ "shas": "903fdf57bcf14cae9e043c4fbafb911715076dda..f6f1aab236022d2804b6bff6a9d5980814a5bdf1"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-replacement-test",
@@ -128,9 +164,19 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "b2de8add90f64f679d620edb09f78d9ef7b77619",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index dbef050..1ee42eb 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-x <= y;",
+ "-x < y;",
+ " x < y;",
+ "+x <= y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "bcaefd0ef86be7154397ea562fe2f42310be20fb"
+ "shas": "f6f1aab236022d2804b6bff6a9d5980814a5bdf1..55e87f9b00be4efdd35b68a61ac0c00bd6adc835"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-test",
@@ -159,9 +205,17 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "bcaefd0ef86be7154397ea562fe2f42310be20fb",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index 1ee42eb..3be8450 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1,2 +1 @@",
+ "-x < y;",
+ " x <= y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d662d575c343d9a108c7cd3b2c245afe697dc54b"
+ "shas": "55e87f9b00be4efdd35b68a61ac0c00bd6adc835..436b0dd39bce7222b6173e02af06a76e64862bd3"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-rest-test",
@@ -190,7 +244,14 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "d662d575c343d9a108c7cd3b2c245afe697dc54b",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index 3be8450..e69de29 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1 +0,0 @@",
+ "-x <= y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3b37b1f1ec583cf921f87b304b606d12b388bcd5"
+ "shas": "436b0dd39bce7222b6173e02af06a76e64862bd3..eaeb10729b105d290f4091fea5f04c34030bb5a5"
}]
diff --git a/test/corpus/diff-summaries/javascript/return-statement.json b/test/corpus/diff-summaries/javascript/return-statement.json
index e080b8a1c..b0c4da35e 100644
--- a/test/corpus/diff-summaries/javascript/return-statement.json
+++ b/test/corpus/diff-summaries/javascript/return-statement.json
@@ -25,9 +25,16 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "1c17753ae9931d9d5b151bab4498c78c5b31c6c1",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index e69de29..6315029 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -0,0 +1 @@",
+ "+return 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b4343e930cea28d8cab6239119d9f3bd801f6cdd"
+ "shas": "2795ba48a13af4b2c6f240761fd880dc6cd10c2b..65e3958e72f9b522fb419169e1dc79619e10fb0e"
}
,{
"testCaseDescription": "javascript-return-statement-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "b4343e930cea28d8cab6239119d9f3bd801f6cdd",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index 6315029..22dde95 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1 +1,3 @@",
+ "+return;",
+ "+return 5;",
+ " return 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "904db501205097a5aa8b10310a4275a851fed123"
+ "shas": "65e3958e72f9b522fb419169e1dc79619e10fb0e..908a90ee504807c1ddcb0e7484d59bb97281136b"
}
,{
"testCaseDescription": "javascript-return-statement-delete-insert-test",
@@ -102,9 +118,19 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "904db501205097a5aa8b10310a4275a851fed123",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index 22dde95..522349c 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-return;",
+ "+return 5;",
+ " return 5;",
+ " return 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4b5192c2450c8d1a41b495dbfbe15300a8adc32a"
+ "shas": "908a90ee504807c1ddcb0e7484d59bb97281136b..20240a05b2905df70c1ee93e3e6b9c931f2959cf"
}
,{
"testCaseDescription": "javascript-return-statement-replacement-test",
@@ -133,9 +159,19 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "4b5192c2450c8d1a41b495dbfbe15300a8adc32a",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index 522349c..22dde95 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-return 5;",
+ "+return;",
+ " return 5;",
+ " return 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "66d5eba60e4744e3ed7407063dfb99b56511cdaf"
+ "shas": "20240a05b2905df70c1ee93e3e6b9c931f2959cf..13392621e30661ca237d268f3ef50e3c7012ae05"
}
,{
"testCaseDescription": "javascript-return-statement-delete-replacement-test",
@@ -194,9 +230,19 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "66d5eba60e4744e3ed7407063dfb99b56511cdaf",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index 22dde95..4d44d6a 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-return;",
+ "-return 5;",
+ " return 5;",
+ "+return;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b7310d5f2ab42c077dd6407c85ee25bb83b8611a"
+ "shas": "13392621e30661ca237d268f3ef50e3c7012ae05..fba0fb892c46997d3c955a13380af9805300ca83"
}
,{
"testCaseDescription": "javascript-return-statement-delete-test",
@@ -225,9 +271,17 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "b7310d5f2ab42c077dd6407c85ee25bb83b8611a",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index 4d44d6a..f312410 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1,2 +1 @@",
+ "-return 5;",
+ " return;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7a76436c3b078dbcfeb060bda0fa0b1cede57295"
+ "shas": "fba0fb892c46997d3c955a13380af9805300ca83..81f231c35cf307c855a8fead87315cb8828c2371"
}
,{
"testCaseDescription": "javascript-return-statement-delete-rest-test",
@@ -256,7 +310,14 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "7a76436c3b078dbcfeb060bda0fa0b1cede57295",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index f312410..e69de29 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1 +0,0 @@",
+ "-return;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "53a957ef4eb59591aa292324c9d8a45e7b4ef059"
+ "shas": "81f231c35cf307c855a8fead87315cb8828c2371..5d2db352ed0e33bb51a7f2330066274984490127"
}]
diff --git a/test/corpus/diff-summaries/javascript/string.json b/test/corpus/diff-summaries/javascript/string.json
index 033517c56..f874ef732 100644
--- a/test/corpus/diff-summaries/javascript/string.json
+++ b/test/corpus/diff-summaries/javascript/string.json
@@ -25,9 +25,16 @@
"filePaths": [
"string.js"
],
- "sha1": "ee6b3d5d274912c071eadd10cb5bea9b96b30cb8",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index e69de29..ea5bd42 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -0,0 +1 @@",
+ "+'A string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "46e49e15b25e27b6aeebdc7948666e0f8533b68d"
+ "shas": "c1ec2fd690eae01418882f3dbba8b6a5c0c3c2eb..dd9d769102a7c17e08e27bae6e4e070a6677cd7f"
}
,{
"testCaseDescription": "javascript-string-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"string.js"
],
- "sha1": "46e49e15b25e27b6aeebdc7948666e0f8533b68d",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index ea5bd42..5cef047 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1 +1,3 @@",
+ "+'A different string with \"double\" quotes';",
+ "+'A string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "085670c25a2ad28cfb1320d941784517513062b6"
+ "shas": "dd9d769102a7c17e08e27bae6e4e070a6677cd7f..6504adbbbbdb0f45a0fba583ccb72ff50cdf8349"
}
,{
"testCaseDescription": "javascript-string-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"string.js"
],
- "sha1": "085670c25a2ad28cfb1320d941784517513062b6",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index 5cef047..7af39a5 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1,3 +1,3 @@",
+ "-'A different string with \"double\" quotes';",
+ "+'A string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "86d28d133e9e7812e18d87b3660360c044e6c21f"
+ "shas": "6504adbbbbdb0f45a0fba583ccb72ff50cdf8349..d39f387280812bce0247667978d542ebe0d27bcb"
}
,{
"testCaseDescription": "javascript-string-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"string.js"
],
- "sha1": "86d28d133e9e7812e18d87b3660360c044e6c21f",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index 7af39a5..5cef047 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1,3 +1,3 @@",
+ "-'A string with \"double\" quotes';",
+ "+'A different string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5dd032df5f467350f02886351995347032be9029"
+ "shas": "d39f387280812bce0247667978d542ebe0d27bcb..b2f472510952cefbc5514307177170e71e3599ec"
}
,{
"testCaseDescription": "javascript-string-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"string.js"
],
- "sha1": "5dd032df5f467350f02886351995347032be9029",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index 5cef047..8dd4514 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1,3 +1,2 @@",
+ "-'A different string with \"double\" quotes';",
+ "-'A string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';",
+ "+'A different string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5f90ef17fb687829457231c9d8faf67867265874"
+ "shas": "b2f472510952cefbc5514307177170e71e3599ec..e83edaaa1afe0823f876025cf3b281bf6f6ab951"
}
,{
"testCaseDescription": "javascript-string-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"string.js"
],
- "sha1": "5f90ef17fb687829457231c9d8faf67867265874",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index 8dd4514..95fbde5 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1,2 +1 @@",
+ "-'A string with \"double\" quotes';",
+ " 'A different string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1085f7bd7baaf6d7417b077dd9eebb1e67b7f87a"
+ "shas": "e83edaaa1afe0823f876025cf3b281bf6f6ab951..b00ba4fad86fcb97c8703641c255c5ca427424eb"
}
,{
"testCaseDescription": "javascript-string-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"string.js"
],
- "sha1": "1085f7bd7baaf6d7417b077dd9eebb1e67b7f87a",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index 95fbde5..e69de29 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1 +0,0 @@",
+ "-'A different string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "616022d16e903375ee8cb705926e3130e700baa1"
+ "shas": "b00ba4fad86fcb97c8703641c255c5ca427424eb..aa6143f1a8ae9ca9b1ee3577121858208df3cce0"
}]
diff --git a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json
index bc2ad74ec..b334fc8c8 100644
--- a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json
+++ b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json
@@ -25,9 +25,16 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "05616ce185cfef047b0a9726d34dc39afb476f00",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index e69de29..6b6d48d 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -0,0 +1 @@",
+ "+y[\"x\"] = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0c7e6867532467399fc151517f78fc8c0c52a015"
+ "shas": "faf582893e706ae259a0482d65d424fbcf137bb2..b59647bbb7592da11c7d4ac78458e63e854b04f3"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "0c7e6867532467399fc151517f78fc8c0c52a015",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index 6b6d48d..17d3ff4 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1 +1,3 @@",
+ "+y[\"x\"] = 1;",
+ "+y[\"x\"] = 0;",
+ " y[\"x\"] = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2fdfaac21ec4632be6f13b8380652b27229141be"
+ "shas": "b59647bbb7592da11c7d4ac78458e63e854b04f3..8b0173919309e1b0e73ab4a4a4fcd8dd02bc0ccb"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "2fdfaac21ec4632be6f13b8380652b27229141be",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index 17d3ff4..d856ac0 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-y[\"x\"] = 1;",
+ "+y[\"x\"] = 0;",
+ " y[\"x\"] = 0;",
+ " y[\"x\"] = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f24a0f5be115b8f6ac2024ccf2b181f8b90bea47"
+ "shas": "8b0173919309e1b0e73ab4a4a4fcd8dd02bc0ccb..461eebed467430133c1996ed21dd6e72dd4f06ac"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "f24a0f5be115b8f6ac2024ccf2b181f8b90bea47",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index d856ac0..17d3ff4 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-y[\"x\"] = 0;",
+ "+y[\"x\"] = 1;",
+ " y[\"x\"] = 0;",
+ " y[\"x\"] = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a72febc32a9a1b8c24c64ef5adf66f5b54b57265"
+ "shas": "461eebed467430133c1996ed21dd6e72dd4f06ac..689acd0e8c575ae20e8d6acaa4522119800c3a39"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "a72febc32a9a1b8c24c64ef5adf66f5b54b57265",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index 17d3ff4..cdcb426 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1,3 +1,2 @@",
+ "-y[\"x\"] = 1;",
+ "-y[\"x\"] = 0;",
+ " y[\"x\"] = 0;",
+ "+y[\"x\"] = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c49cc2f5d46d18f3fa6427ba257b51b3de7b1b03"
+ "shas": "689acd0e8c575ae20e8d6acaa4522119800c3a39..a124eee21e5e3f952e498fb2175d1497ca06aa13"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "c49cc2f5d46d18f3fa6427ba257b51b3de7b1b03",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index cdcb426..0407c3a 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1,2 +1 @@",
+ "-y[\"x\"] = 0;",
+ " y[\"x\"] = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b656e126f88cd358455eb7aaccc40ecd359498f4"
+ "shas": "a124eee21e5e3f952e498fb2175d1497ca06aa13..194ef1fb19bf18a70a7e1a0dd198c832d2383bd9"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "b656e126f88cd358455eb7aaccc40ecd359498f4",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index 0407c3a..e69de29 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1 +0,0 @@",
+ "-y[\"x\"] = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "653a2a2b908c1963d4682a6e4b6e89f1aa17b275"
+ "shas": "194ef1fb19bf18a70a7e1a0dd198c832d2383bd9..ec86aaba01801d01aca70fd31403642be1e2d438"
}]
diff --git a/test/corpus/diff-summaries/javascript/subscript-access-string.json b/test/corpus/diff-summaries/javascript/subscript-access-string.json
index c0e3dc377..13e2db731 100644
--- a/test/corpus/diff-summaries/javascript/subscript-access-string.json
+++ b/test/corpus/diff-summaries/javascript/subscript-access-string.json
@@ -25,9 +25,16 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "4c278dba39541a15d92a474e30abd18009989d53",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index e69de29..4293717 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -0,0 +1 @@",
+ "+x[\"some-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3a94ecc5640d497edc136a58e3732b9da4f951b0"
+ "shas": "b6fd9fdbec2e79ee92f6829605a2e1a54a1784ba..bf933db8b20ff7bc2d86eb5a8e8082fd78234e87"
}
,{
"testCaseDescription": "javascript-subscript-access-string-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "3a94ecc5640d497edc136a58e3732b9da4f951b0",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index 4293717..4293009 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1 +1,3 @@",
+ "+x[\"some-other-string\"];",
+ "+x[\"some-string\"];",
+ " x[\"some-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d421f5b1225655cca2faaf945f8ad3b9576b519e"
+ "shas": "bf933db8b20ff7bc2d86eb5a8e8082fd78234e87..3cc4eb9c46cd85ade63c176295763ab093268536"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "d421f5b1225655cca2faaf945f8ad3b9576b519e",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index 4293009..c53d07b 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1,3 +1,3 @@",
+ "-x[\"some-other-string\"];",
+ "+x[\"some-string\"];",
+ " x[\"some-string\"];",
+ " x[\"some-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a013d3d8115320af6d71bc7a5aa4043ab9ff100c"
+ "shas": "3cc4eb9c46cd85ade63c176295763ab093268536..182d9efc50b49dfedd82b47b3382606f3bd57567"
}
,{
"testCaseDescription": "javascript-subscript-access-string-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "a013d3d8115320af6d71bc7a5aa4043ab9ff100c",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index c53d07b..4293009 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1,3 +1,3 @@",
+ "-x[\"some-string\"];",
+ "+x[\"some-other-string\"];",
+ " x[\"some-string\"];",
+ " x[\"some-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "723551ba66cd479e5b91e632627e0ebb836dbe38"
+ "shas": "182d9efc50b49dfedd82b47b3382606f3bd57567..203a1ff0e0cd35b08ded73803e92f3094a9a0bd7"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "723551ba66cd479e5b91e632627e0ebb836dbe38",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index 4293009..89c1bc2 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1,3 +1,2 @@",
+ "-x[\"some-other-string\"];",
+ "-x[\"some-string\"];",
+ " x[\"some-string\"];",
+ "+x[\"some-other-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "389fcec55bd47072d0d017834f5acfffdcbc3fa9"
+ "shas": "203a1ff0e0cd35b08ded73803e92f3094a9a0bd7..d4061981099d5b4d806f6786addfa3faba8b1dfe"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "389fcec55bd47072d0d017834f5acfffdcbc3fa9",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index 89c1bc2..758f8e7 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1,2 +1 @@",
+ "-x[\"some-string\"];",
+ " x[\"some-other-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e2d778b8f360801caff8b635964a37af1c03ca47"
+ "shas": "d4061981099d5b4d806f6786addfa3faba8b1dfe..0b3a01d8665ee9e2126b68009c7a8c9d41fca3c8"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "e2d778b8f360801caff8b635964a37af1c03ca47",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index 758f8e7..e69de29 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1 +0,0 @@",
+ "-x[\"some-other-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d634acd5aed3ab7ef4a9914234758a3bf356d2c4"
+ "shas": "0b3a01d8665ee9e2126b68009c7a8c9d41fca3c8..71feda9fd80ab60adab5cf81748710b2a610173f"
}]
diff --git a/test/corpus/diff-summaries/javascript/subscript-access-variable.json b/test/corpus/diff-summaries/javascript/subscript-access-variable.json
index 827e49866..5e7e265f2 100644
--- a/test/corpus/diff-summaries/javascript/subscript-access-variable.json
+++ b/test/corpus/diff-summaries/javascript/subscript-access-variable.json
@@ -25,9 +25,16 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "3703258beda4cec843b8f1d61576e214ffd3651b",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index e69de29..9a7b3d3 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -0,0 +1 @@",
+ "+x[someVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ebb7cf11c3f883bf719a026946a73d5a81d19a6e"
+ "shas": "bcba202e709aea072f614c126e2a5bb356cbf3fe..f506206202b7ba25d0d7002482361368d4484792"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "ebb7cf11c3f883bf719a026946a73d5a81d19a6e",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index 9a7b3d3..000d190 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1 +1,3 @@",
+ "+x[someOtherVariable];",
+ "+x[someVariable];",
+ " x[someVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3d3432eb1d2d28c69db5dbbead233987b4642adc"
+ "shas": "f506206202b7ba25d0d7002482361368d4484792..bc70d1984738705b4df815056d104a56f917365b"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "3d3432eb1d2d28c69db5dbbead233987b4642adc",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index 000d190..01f61ef 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1,3 +1,3 @@",
+ "-x[someOtherVariable];",
+ "+x[someVariable];",
+ " x[someVariable];",
+ " x[someVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6f03d88dc0b6f112255e8813d62c09437ffeb24c"
+ "shas": "bc70d1984738705b4df815056d104a56f917365b..912cf4a3c64ca194b5497e5fd9730ea2311d3947"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "6f03d88dc0b6f112255e8813d62c09437ffeb24c",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index 01f61ef..000d190 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1,3 +1,3 @@",
+ "-x[someVariable];",
+ "+x[someOtherVariable];",
+ " x[someVariable];",
+ " x[someVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c8843b7af25558a8470fd3fc8f70df4ec9e4c108"
+ "shas": "912cf4a3c64ca194b5497e5fd9730ea2311d3947..2b501586eba02bbd8e3ea2313ae892d24672a95d"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "c8843b7af25558a8470fd3fc8f70df4ec9e4c108",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index 000d190..2aaae7e 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1,3 +1,2 @@",
+ "-x[someOtherVariable];",
+ "-x[someVariable];",
+ " x[someVariable];",
+ "+x[someOtherVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "36ef554534ca14a76e650037a2913b49f2b22042"
+ "shas": "2b501586eba02bbd8e3ea2313ae892d24672a95d..188b43fc4ab2de0e499492f21c5b24308c26e908"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "36ef554534ca14a76e650037a2913b49f2b22042",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index 2aaae7e..baa3661 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1,2 +1 @@",
+ "-x[someVariable];",
+ " x[someOtherVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "af1714a831574736d7472d7b88e9c7160ffcd12d"
+ "shas": "188b43fc4ab2de0e499492f21c5b24308c26e908..386de21b188a783b6a0a9b5c024f0c92082dbfde"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "af1714a831574736d7472d7b88e9c7160ffcd12d",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index baa3661..e69de29 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1 +0,0 @@",
+ "-x[someOtherVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4c278dba39541a15d92a474e30abd18009989d53"
+ "shas": "386de21b188a783b6a0a9b5c024f0c92082dbfde..b6fd9fdbec2e79ee92f6829605a2e1a54a1784ba"
}]
diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json
index 41b77f511..9bd205100 100644
--- a/test/corpus/diff-summaries/javascript/switch-statement.json
+++ b/test/corpus/diff-summaries/javascript/switch-statement.json
@@ -25,9 +25,16 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "3061e328305d93ca2fd3a8aa7a86d645c4c28b15",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index e69de29..5481c49 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -0,0 +1 @@",
+ "+switch (1) { case 1: 1; case 2: 1; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5f53dc879b334542448ffa34bdc4c8577fa2631c"
+ "shas": "8f7edd21ecef61769b82fb5a60a881f31ce30a01..9e6646e9f984497bc80a1c1f1afb86eb869c9b26"
}
,{
"testCaseDescription": "javascript-switch-statement-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "5f53dc879b334542448ffa34bdc4c8577fa2631c",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index 5481c49..ffd4a32 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1 +1,3 @@",
+ "+switch (2) { case 1: 1; case 2: 2; case 3: 3; };",
+ "+switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "cd94b5a63c7f3e1b4030abf1594df447a408bd53"
+ "shas": "9e6646e9f984497bc80a1c1f1afb86eb869c9b26..887d9088c295dc7a59711a02769e0754c6d1fa33"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-insert-test",
@@ -105,7 +121,7 @@
}
]
},
- "summary": "Replaced '2' with '1'"
+ "summary": "Replaced '2' with '1' in the '1' switch statement"
},
{
"span": {
@@ -132,7 +148,7 @@
}
]
},
- "summary": "Replaced '2' with '1'"
+ "summary": "Replaced '2' with '1' in the '2' case statement"
}
]
},
@@ -141,9 +157,19 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "cd94b5a63c7f3e1b4030abf1594df447a408bd53",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index ffd4a32..302fb8b 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-switch (2) { case 1: 1; case 2: 2; case 3: 3; };",
+ "+switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "bf2bf68e09cff917b1f1e995fb4dea6fa856233d"
+ "shas": "887d9088c295dc7a59711a02769e0754c6d1fa33..ba0bf7fe9de15a5f734f4e4c6059ce15c34e8311"
}
,{
"testCaseDescription": "javascript-switch-statement-replacement-test",
@@ -175,7 +201,7 @@
}
]
},
- "summary": "Replaced '1' with '2'"
+ "summary": "Replaced '1' with '2' in the '2' switch statement"
},
{
"span": {
@@ -202,7 +228,7 @@
}
]
},
- "summary": "Replaced '1' with '2'"
+ "summary": "Replaced '1' with '2' in the '2' case statement"
}
]
},
@@ -211,9 +237,19 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "bf2bf68e09cff917b1f1e995fb4dea6fa856233d",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index 302fb8b..ffd4a32 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ "+switch (2) { case 1: 1; case 2: 2; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "bd8d8bb98201860e195a9d64d0ef921727472476"
+ "shas": "ba0bf7fe9de15a5f734f4e4c6059ce15c34e8311..213e3cb9828fdcbfe60dea518fb77b1896af15bb"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-replacement-test",
@@ -272,9 +308,19 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "bd8d8bb98201860e195a9d64d0ef921727472476",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index ffd4a32..9b60579 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-switch (2) { case 1: 1; case 2: 2; case 3: 3; };",
+ "-switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ "+switch (2) { case 1: 1; case 2: 2; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a4e7ca238ba4f2e84929de265104ee0370233f82"
+ "shas": "213e3cb9828fdcbfe60dea518fb77b1896af15bb..a818910ed9354ea4b6070e11af8de9cefd66aedf"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-test",
@@ -303,9 +349,17 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "a4e7ca238ba4f2e84929de265104ee0370233f82",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index 9b60579..374091f 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1,2 +1 @@",
+ "-switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (2) { case 1: 1; case 2: 2; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "89100f872e690353e3171008af10bb9be2f6beb3"
+ "shas": "a818910ed9354ea4b6070e11af8de9cefd66aedf..db5abd71dd4f34b20163d37657b839707b279e09"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-rest-test",
@@ -334,7 +388,14 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "89100f872e690353e3171008af10bb9be2f6beb3",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index 374091f..e69de29 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1 +0,0 @@",
+ "-switch (2) { case 1: 1; case 2: 2; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "be60a15b22146780f1f1a090b8550ce29929e830"
+ "shas": "db5abd71dd4f34b20163d37657b839707b279e09..8e3f45940f773e7849a53fefdaeb52a682a6a488"
}]
diff --git a/test/corpus/diff-summaries/javascript/template-string.json b/test/corpus/diff-summaries/javascript/template-string.json
index 5699861fd..0e00c7bd5 100644
--- a/test/corpus/diff-summaries/javascript/template-string.json
+++ b/test/corpus/diff-summaries/javascript/template-string.json
@@ -25,9 +25,16 @@
"filePaths": [
"template-string.js"
],
- "sha1": "2dee917afc37bf88e9b7405744f9b8877a4c68c3",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index e69de29..01f859b 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -0,0 +1 @@",
+ "+`one line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9174b705b2caecad6cf2b23e992d92c62edfa8dc"
+ "shas": "dffe792710a5ad52de12ed62e48340a71e5c9227..4f86472b03fd24538a67565981a8d25700240497"
}
,{
"testCaseDescription": "javascript-template-string-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"template-string.js"
],
- "sha1": "9174b705b2caecad6cf2b23e992d92c62edfa8dc",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 01f859b..777fde6 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1 +1,3 @@",
+ "+`multi line`",
+ "+`one line`",
+ " `one line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "50efce34c0f5da6ca5ea7d712ee7d9269680ecd5"
+ "shas": "4f86472b03fd24538a67565981a8d25700240497..8e2e8be8c6d60e68e5851f727da2c71ace094f34"
}
,{
"testCaseDescription": "javascript-template-string-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"template-string.js"
],
- "sha1": "50efce34c0f5da6ca5ea7d712ee7d9269680ecd5",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 777fde6..657129f 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1,3 +1,3 @@",
+ "-`multi line`",
+ "+`one line`",
+ " `one line`",
+ " `one line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "cb5213d63f493b86560dffcb1e72fa9e64173387"
+ "shas": "8e2e8be8c6d60e68e5851f727da2c71ace094f34..a481b18c353836ec0291fd6a2e9ea424de6b7a8c"
}
,{
"testCaseDescription": "javascript-template-string-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"template-string.js"
],
- "sha1": "cb5213d63f493b86560dffcb1e72fa9e64173387",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 657129f..777fde6 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1,3 +1,3 @@",
+ "-`one line`",
+ "+`multi line`",
+ " `one line`",
+ " `one line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7e8767a07f7aac3e58df81968669f9df43043f19"
+ "shas": "a481b18c353836ec0291fd6a2e9ea424de6b7a8c..671ff7c523a3b938440bc9534540d94f391acd9e"
}
,{
"testCaseDescription": "javascript-template-string-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"template-string.js"
],
- "sha1": "7e8767a07f7aac3e58df81968669f9df43043f19",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 777fde6..2b8c0dd 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1,3 +1,2 @@",
+ "-`multi line`",
+ "-`one line`",
+ " `one line`",
+ "+`multi line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3d5a90bc9f90b8581ccab9c0d56841554233354d"
+ "shas": "671ff7c523a3b938440bc9534540d94f391acd9e..ba89b5cfbffb97d143c19125b8ed8e468113cd32"
}
,{
"testCaseDescription": "javascript-template-string-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"template-string.js"
],
- "sha1": "3d5a90bc9f90b8581ccab9c0d56841554233354d",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 2b8c0dd..399f117 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1,2 +1 @@",
+ "-`one line`",
+ " `multi line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5b7f9d093d86d267d3743848751be2d07944891a"
+ "shas": "ba89b5cfbffb97d143c19125b8ed8e468113cd32..ce95b79e18d47915e2eecdef309a73b64417d53c"
}
,{
"testCaseDescription": "javascript-template-string-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"template-string.js"
],
- "sha1": "5b7f9d093d86d267d3743848751be2d07944891a",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 399f117..e69de29 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1 +0,0 @@",
+ "-`multi line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "59c52a0ddb5e652e5b5108d0724541989a6d83aa"
+ "shas": "ce95b79e18d47915e2eecdef309a73b64417d53c..75f87f22428c68545ebb3f876a1b09caf59d75c9"
}]
diff --git a/test/corpus/diff-summaries/javascript/ternary.json b/test/corpus/diff-summaries/javascript/ternary.json
index 1b0bcec55..bdaf1034b 100644
--- a/test/corpus/diff-summaries/javascript/ternary.json
+++ b/test/corpus/diff-summaries/javascript/ternary.json
@@ -25,9 +25,16 @@
"filePaths": [
"ternary.js"
],
- "sha1": "26df3b54cd036f1ed2bff8a0ca225ad680e23432",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index e69de29..a62be2e 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -0,0 +1 @@",
+ "+condition ? case1 : case2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "275a09584d8d33199f73045e1f070e2b9a714fc9"
+ "shas": "0ccf8092231ebc8ac92cc60fe614f1681bc03a89..9667649b2849f1e590a44feec0a6c62c3c2135cc"
}
,{
"testCaseDescription": "javascript-ternary-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"ternary.js"
],
- "sha1": "275a09584d8d33199f73045e1f070e2b9a714fc9",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index a62be2e..17b4f8e 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1 +1,3 @@",
+ "+x.y = some.condition ? some.case : some.other.case;",
+ "+condition ? case1 : case2;",
+ " condition ? case1 : case2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c3245f5cb3dca8b5fcf3d1ea1e16e77602560442"
+ "shas": "9667649b2849f1e590a44feec0a6c62c3c2135cc..3d5e67c4dc00b3bbf85a3bbe1afd847c77703bbf"
}
,{
"testCaseDescription": "javascript-ternary-delete-insert-test",
@@ -117,9 +133,19 @@
"filePaths": [
"ternary.js"
],
- "sha1": "c3245f5cb3dca8b5fcf3d1ea1e16e77602560442",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index 17b4f8e..aedee54 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1,3 +1,3 @@",
+ "-x.y = some.condition ? some.case : some.other.case;",
+ "+condition ? case1 : case2;",
+ " condition ? case1 : case2;",
+ " condition ? case1 : case2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "dcc065cf8b2bab2519aaaac434f17e88abe22965"
+ "shas": "3d5e67c4dc00b3bbf85a3bbe1afd847c77703bbf..6cba7001515f3956a69b73f69608b7cca7f625f0"
}
,{
"testCaseDescription": "javascript-ternary-replacement-test",
@@ -163,9 +189,19 @@
"filePaths": [
"ternary.js"
],
- "sha1": "dcc065cf8b2bab2519aaaac434f17e88abe22965",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index aedee54..17b4f8e 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1,3 +1,3 @@",
+ "-condition ? case1 : case2;",
+ "+x.y = some.condition ? some.case : some.other.case;",
+ " condition ? case1 : case2;",
+ " condition ? case1 : case2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1d1e9bb19ab493af77f9e987c01bdacd45b8db15"
+ "shas": "6cba7001515f3956a69b73f69608b7cca7f625f0..7e01f0008705a5f7ffced4f2b9cfaf1431c408fb"
}
,{
"testCaseDescription": "javascript-ternary-delete-replacement-test",
@@ -224,9 +260,19 @@
"filePaths": [
"ternary.js"
],
- "sha1": "1d1e9bb19ab493af77f9e987c01bdacd45b8db15",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index 17b4f8e..6fa999d 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1,3 +1,2 @@",
+ "-x.y = some.condition ? some.case : some.other.case;",
+ "-condition ? case1 : case2;",
+ " condition ? case1 : case2;",
+ "+x.y = some.condition ? some.case : some.other.case;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9d63fa6989fd2bfaffab6531784de14af800bff7"
+ "shas": "7e01f0008705a5f7ffced4f2b9cfaf1431c408fb..7d3393632b17cc8c73de9dac1a7538f7fd60e2ca"
}
,{
"testCaseDescription": "javascript-ternary-delete-test",
@@ -255,9 +301,17 @@
"filePaths": [
"ternary.js"
],
- "sha1": "9d63fa6989fd2bfaffab6531784de14af800bff7",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index 6fa999d..b63b46d 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1,2 +1 @@",
+ "-condition ? case1 : case2;",
+ " x.y = some.condition ? some.case : some.other.case;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8e67b7193d675b0801d962b2fc9d4e8dfdc69936"
+ "shas": "7d3393632b17cc8c73de9dac1a7538f7fd60e2ca..361260c5dc31603f665fefc889640330903dbafd"
}
,{
"testCaseDescription": "javascript-ternary-delete-rest-test",
@@ -286,7 +340,14 @@
"filePaths": [
"ternary.js"
],
- "sha1": "8e67b7193d675b0801d962b2fc9d4e8dfdc69936",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index b63b46d..e69de29 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1 +0,0 @@",
+ "-x.y = some.condition ? some.case : some.other.case;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0f2f0f6f7ae9bb6ee07a66ff1021c512e7ff727a"
+ "shas": "361260c5dc31603f665fefc889640330903dbafd..38dbecd6735244d4c2c50c6608e64fd7df72b900"
}]
diff --git a/test/corpus/diff-summaries/javascript/this-expression.json b/test/corpus/diff-summaries/javascript/this-expression.json
index eaf14dd5d..c15e3aec7 100644
--- a/test/corpus/diff-summaries/javascript/this-expression.json
+++ b/test/corpus/diff-summaries/javascript/this-expression.json
@@ -25,9 +25,16 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "b3470025ee263454110f25252e09c359560d1bd5",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index e69de29..b251f26 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -0,0 +1 @@",
+ "+this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3fee11eb6f5c99cb939a8b729a42061b3fe589c6"
+ "shas": "5180fa74c7ae39b3c2cb94b9b5498307af385e5c..98e4bf8c567fd1203aa3d1c3b9e9dc58d5733e11"
}
,{
"testCaseDescription": "javascript-this-expression-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "3fee11eb6f5c99cb939a8b729a42061b3fe589c6",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index b251f26..5804743 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1 +1,3 @@",
+ "+return this;",
+ "+this;",
+ " this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ea6e2908e34461c585e71957c320f4eeb8595a04"
+ "shas": "98e4bf8c567fd1203aa3d1c3b9e9dc58d5733e11..9dd112b28d5a97a59a847018e58f3926ccf46e56"
}
,{
"testCaseDescription": "javascript-this-expression-delete-insert-test",
@@ -117,9 +133,19 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "ea6e2908e34461c585e71957c320f4eeb8595a04",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index 5804743..3c82a23 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1,3 +1,3 @@",
+ "-return this;",
+ "+this;",
+ " this;",
+ " this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7bd744a61db05a1b11c1044313dbdb123d290bf6"
+ "shas": "9dd112b28d5a97a59a847018e58f3926ccf46e56..d1b36cdc475a6f7ea16558b4269f3e3c18758dfa"
}
,{
"testCaseDescription": "javascript-this-expression-replacement-test",
@@ -163,9 +189,19 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "7bd744a61db05a1b11c1044313dbdb123d290bf6",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index 3c82a23..5804743 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1,3 +1,3 @@",
+ "-this;",
+ "+return this;",
+ " this;",
+ " this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e4f1825876d89ecaeb1e2b78e95ae197e26d5d3c"
+ "shas": "d1b36cdc475a6f7ea16558b4269f3e3c18758dfa..efc36cfae7c31ef3d4f2052a0c79fe592ab2aa58"
}
,{
"testCaseDescription": "javascript-this-expression-delete-replacement-test",
@@ -224,9 +260,19 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "e4f1825876d89ecaeb1e2b78e95ae197e26d5d3c",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index 5804743..81aca89 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1,3 +1,2 @@",
+ "-return this;",
+ "-this;",
+ " this;",
+ "+return this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "31d93d5253b1465ad809f0f4feb42336025cea63"
+ "shas": "efc36cfae7c31ef3d4f2052a0c79fe592ab2aa58..531a5b86388175804b734a10ace1c7645169154b"
}
,{
"testCaseDescription": "javascript-this-expression-delete-test",
@@ -255,9 +301,17 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "31d93d5253b1465ad809f0f4feb42336025cea63",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index 81aca89..45c3231 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1,2 +1 @@",
+ "-this;",
+ " return this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "72f5d7c8a95f79aaef409926e8f7e00d7c5bf74d"
+ "shas": "531a5b86388175804b734a10ace1c7645169154b..dfa50df5733740923a1d747f988102b19e9ce7e0"
}
,{
"testCaseDescription": "javascript-this-expression-delete-rest-test",
@@ -286,7 +340,14 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "72f5d7c8a95f79aaef409926e8f7e00d7c5bf74d",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index 45c3231..e69de29 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1 +0,0 @@",
+ "-return this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6d600208cc985a6c0fbbbdbd54227f1010a9bb14"
+ "shas": "dfa50df5733740923a1d747f988102b19e9ce7e0..655d7887b70794042aa3e0f4d6ea174c1b32af1c"
}]
diff --git a/test/corpus/diff-summaries/javascript/throw-statement.json b/test/corpus/diff-summaries/javascript/throw-statement.json
index a943c2e95..9d7d995c0 100644
--- a/test/corpus/diff-summaries/javascript/throw-statement.json
+++ b/test/corpus/diff-summaries/javascript/throw-statement.json
@@ -25,9 +25,16 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "be60a15b22146780f1f1a090b8550ce29929e830",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index e69de29..e2fcb67 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -0,0 +1 @@",
+ "+throw new Error(\"uh oh\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "06ff6b48e424252bf5f7e1734af6be3939c7160a"
+ "shas": "8e3f45940f773e7849a53fefdaeb52a682a6a488..116eb17be5e023970df37ba38884c86aa4cb9dbd"
}
,{
"testCaseDescription": "javascript-throw-statement-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "06ff6b48e424252bf5f7e1734af6be3939c7160a",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index e2fcb67..c0020c8 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1 +1,3 @@",
+ "+throw new Error(\"oooooops\");",
+ "+throw new Error(\"uh oh\");",
+ " throw new Error(\"uh oh\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f1b8b13e67b888546e7f539aa11f39ec0071e984"
+ "shas": "116eb17be5e023970df37ba38884c86aa4cb9dbd..e1a31ba713d3185c274f86dd4e8644740fb7429d"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "f1b8b13e67b888546e7f539aa11f39ec0071e984",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index c0020c8..4644233 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-throw new Error(\"oooooops\");",
+ "+throw new Error(\"uh oh\");",
+ " throw new Error(\"uh oh\");",
+ " throw new Error(\"uh oh\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2547a3a1d8fc60aedb2d5f017318ade862ee3e54"
+ "shas": "e1a31ba713d3185c274f86dd4e8644740fb7429d..dad40ac44ee1763621da95939261c0afc7664ec4"
}
,{
"testCaseDescription": "javascript-throw-statement-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "2547a3a1d8fc60aedb2d5f017318ade862ee3e54",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index 4644233..c0020c8 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-throw new Error(\"uh oh\");",
+ "+throw new Error(\"oooooops\");",
+ " throw new Error(\"uh oh\");",
+ " throw new Error(\"uh oh\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "23c866826fe1d1f041a445cd747ef16e3174122c"
+ "shas": "dad40ac44ee1763621da95939261c0afc7664ec4..6ead807809e97520b2dce628bc592bfa358dd249"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "23c866826fe1d1f041a445cd747ef16e3174122c",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index c0020c8..a1bbf3e 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-throw new Error(\"oooooops\");",
+ "-throw new Error(\"uh oh\");",
+ " throw new Error(\"uh oh\");",
+ "+throw new Error(\"oooooops\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "70db2c7584e6acae05d2d03b49860dc5db393f62"
+ "shas": "6ead807809e97520b2dce628bc592bfa358dd249..c1804715b17f4c02c529052b13f67eab4f85d127"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "70db2c7584e6acae05d2d03b49860dc5db393f62",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index a1bbf3e..cc3c531 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1,2 +1 @@",
+ "-throw new Error(\"uh oh\");",
+ " throw new Error(\"oooooops\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b6610e26a2e5418b434ea25e1227b430961113cc"
+ "shas": "c1804715b17f4c02c529052b13f67eab4f85d127..36892466e1b20aa85270c797d4898149a5456dae"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "b6610e26a2e5418b434ea25e1227b430961113cc",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index cc3c531..e69de29 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1 +0,0 @@",
+ "-throw new Error(\"oooooops\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b52b5d119274b849b6f3a5aa770b5677e0f1ea18"
+ "shas": "36892466e1b20aa85270c797d4898149a5456dae..a5583b5ba5ae300bddff029cb144c539a2cb48fd"
}]
diff --git a/test/corpus/diff-summaries/javascript/true.json b/test/corpus/diff-summaries/javascript/true.json
index 06d25aba4..198bd4dfe 100644
--- a/test/corpus/diff-summaries/javascript/true.json
+++ b/test/corpus/diff-summaries/javascript/true.json
@@ -25,9 +25,16 @@
"filePaths": [
"true.js"
],
- "sha1": "fc80ccb71b0c0f159f05f8232853473f7f64457e",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index e69de29..4203d4b 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -0,0 +1 @@",
+ "+true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1bc0309425daa924ae3ea043487c39b6848c5101"
+ "shas": "bc804312603351b07d0e242d9b3675d646934512..b8a5a66ee0d580e0f5be577ba65a6afe82b8acfe"
}
,{
"testCaseDescription": "javascript-true-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"true.js"
],
- "sha1": "1bc0309425daa924ae3ea043487c39b6848c5101",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index 4203d4b..65b6323 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1 +1,3 @@",
+ "+return true;",
+ "+true;",
+ " true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4ff3fb89e3bdee3acfa7caea5d67cca2f92a7f25"
+ "shas": "b8a5a66ee0d580e0f5be577ba65a6afe82b8acfe..38f0052081cce419eb03bcd07164a3f756a4d014"
}
,{
"testCaseDescription": "javascript-true-delete-insert-test",
@@ -117,9 +133,19 @@
"filePaths": [
"true.js"
],
- "sha1": "4ff3fb89e3bdee3acfa7caea5d67cca2f92a7f25",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index 65b6323..91e1cfc 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1,3 +1,3 @@",
+ "-return true;",
+ "+true;",
+ " true;",
+ " true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c750216e8276e0e09c33035db1b4f84c6b532ea3"
+ "shas": "38f0052081cce419eb03bcd07164a3f756a4d014..514cc9bcf90d8b96eb0f5109b0c84d8136f5e82a"
}
,{
"testCaseDescription": "javascript-true-replacement-test",
@@ -163,9 +189,19 @@
"filePaths": [
"true.js"
],
- "sha1": "c750216e8276e0e09c33035db1b4f84c6b532ea3",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index 91e1cfc..65b6323 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1,3 +1,3 @@",
+ "-true;",
+ "+return true;",
+ " true;",
+ " true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a3f9ee0d3aaa5a315031e3f9b6711995f1737c6b"
+ "shas": "514cc9bcf90d8b96eb0f5109b0c84d8136f5e82a..883bffa8136e0f6cc1fc850f8aab8f69ac48699b"
}
,{
"testCaseDescription": "javascript-true-delete-replacement-test",
@@ -224,9 +260,19 @@
"filePaths": [
"true.js"
],
- "sha1": "a3f9ee0d3aaa5a315031e3f9b6711995f1737c6b",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index 65b6323..48a44d1 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1,3 +1,2 @@",
+ "-return true;",
+ "-true;",
+ " true;",
+ "+return true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8e9e8b1a5a4beb5e33e607dc86b5f45aa694ddf0"
+ "shas": "883bffa8136e0f6cc1fc850f8aab8f69ac48699b..36585335908145fbf9f18eabecb60038b29552f0"
}
,{
"testCaseDescription": "javascript-true-delete-test",
@@ -255,9 +301,17 @@
"filePaths": [
"true.js"
],
- "sha1": "8e9e8b1a5a4beb5e33e607dc86b5f45aa694ddf0",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index 48a44d1..c1c6922 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1,2 +1 @@",
+ "-true;",
+ " return true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ad3373eca4102be0a57a93239b8feec6863dfcbb"
+ "shas": "36585335908145fbf9f18eabecb60038b29552f0..9d5dc3e57ffd189e1482d577bfc73e78e900d42a"
}
,{
"testCaseDescription": "javascript-true-delete-rest-test",
@@ -286,7 +340,14 @@
"filePaths": [
"true.js"
],
- "sha1": "ad3373eca4102be0a57a93239b8feec6863dfcbb",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index c1c6922..e69de29 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1 +0,0 @@",
+ "-return true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "04aded71e587d0bada2c50fd567023d9de7f477c"
+ "shas": "9d5dc3e57ffd189e1482d577bfc73e78e900d42a..a56c14e19dec2910d36460e4fca6496da46f6240"
}]
diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json
index e10f8677d..80e94c7ff 100644
--- a/test/corpus/diff-summaries/javascript/try-statement.json
+++ b/test/corpus/diff-summaries/javascript/try-statement.json
@@ -25,9 +25,16 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "b52b5d119274b849b6f3a5aa770b5677e0f1ea18",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index e69de29..9826f7c 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -0,0 +1 @@",
+ "+try { f; } catch { g; } finally { h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "094ef2fc34540b5768d25ac41b36f5049f29ea4c"
+ "shas": "a5583b5ba5ae300bddff029cb144c539a2cb48fd..d8b7dc1823e1a5b0909865b2d0d40a40f0185e59"
}
,{
"testCaseDescription": "javascript-try-statement-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "094ef2fc34540b5768d25ac41b36f5049f29ea4c",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 9826f7c..7befc1c 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1 +1,3 @@",
+ "+try { f; } catch { h; } finally { g; };",
+ "+try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { g; } finally { h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e3e141029d6dbac080f790734eeae92e3009478c"
+ "shas": "d8b7dc1823e1a5b0909865b2d0d40a40f0185e59..670f6360d76e32d78de98aae0552d153f8dc9a90"
}
,{
"testCaseDescription": "javascript-try-statement-delete-insert-test",
@@ -105,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'h' identifier with the 'g' identifier"
+ "summary": "Replaced the 'h' identifier with the 'g' identifier in the { f; } try statement"
},
{
"span": {
@@ -132,7 +148,7 @@
}
]
},
- "summary": "Replaced the 'g' identifier with the 'h' identifier"
+ "summary": "Replaced the 'g' identifier with the 'h' identifier in the { f; } try statement"
}
]
},
@@ -141,9 +157,19 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "e3e141029d6dbac080f790734eeae92e3009478c",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 7befc1c..94fed9c 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-try { f; } catch { h; } finally { g; };",
+ "+try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { g; } finally { h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e8834151ab8481af32b7f8f21cb3c0ed6eeeb2fe"
+ "shas": "670f6360d76e32d78de98aae0552d153f8dc9a90..64175cdf26b3a3618ea930a705a043f895b3fd09"
}
,{
"testCaseDescription": "javascript-try-statement-replacement-test",
@@ -175,7 +201,7 @@
}
]
},
- "summary": "Replaced the 'g' identifier with the 'h' identifier"
+ "summary": "Replaced the 'g' identifier with the 'h' identifier in the { f; } try statement"
},
{
"span": {
@@ -202,7 +228,7 @@
}
]
},
- "summary": "Replaced the 'h' identifier with the 'g' identifier"
+ "summary": "Replaced the 'h' identifier with the 'g' identifier in the { f; } try statement"
}
]
},
@@ -211,9 +237,19 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "e8834151ab8481af32b7f8f21cb3c0ed6eeeb2fe",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 94fed9c..7befc1c 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-try { f; } catch { g; } finally { h; };",
+ "+try { f; } catch { h; } finally { g; };",
+ " try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { g; } finally { h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d0a7a97704a756ed71be5705b5ad38e182a976a4"
+ "shas": "64175cdf26b3a3618ea930a705a043f895b3fd09..42c1509a343741e5dd1c1bfcb86fb8745b60824d"
}
,{
"testCaseDescription": "javascript-try-statement-delete-replacement-test",
@@ -272,9 +308,19 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "d0a7a97704a756ed71be5705b5ad38e182a976a4",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 7befc1c..8ab70e0 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-try { f; } catch { h; } finally { g; };",
+ "-try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { g; } finally { h; };",
+ "+try { f; } catch { h; } finally { g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "adb14c0e7eb9b014f719a240bf861b6e5e9b2e79"
+ "shas": "42c1509a343741e5dd1c1bfcb86fb8745b60824d..400e89f91ea35a78dd70b46c3bc204c5aed26b7f"
}
,{
"testCaseDescription": "javascript-try-statement-delete-test",
@@ -303,9 +349,17 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "adb14c0e7eb9b014f719a240bf861b6e5e9b2e79",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 8ab70e0..024f88a 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1,2 +1 @@",
+ "-try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { h; } finally { g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2060834aab0b12a63118aa57fad88ea1808445c5"
+ "shas": "400e89f91ea35a78dd70b46c3bc204c5aed26b7f..f97dd13575c5a030192a9abd5e4992a51afc050f"
}
,{
"testCaseDescription": "javascript-try-statement-delete-rest-test",
@@ -334,7 +388,14 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "2060834aab0b12a63118aa57fad88ea1808445c5",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 024f88a..e69de29 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1 +0,0 @@",
+ "-try { f; } catch { h; } finally { g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "97a7c83a9e020ac198c1fbf23d38b3089f4484b1"
+ "shas": "f97dd13575c5a030192a9abd5e4992a51afc050f..734bede3c6c3771f011aa729a417011d310ec5cc"
}]
diff --git a/test/corpus/diff-summaries/javascript/type-operator.json b/test/corpus/diff-summaries/javascript/type-operator.json
index 0153f3784..4d3b4ab31 100644
--- a/test/corpus/diff-summaries/javascript/type-operator.json
+++ b/test/corpus/diff-summaries/javascript/type-operator.json
@@ -25,9 +25,16 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "0f2f0f6f7ae9bb6ee07a66ff1021c512e7ff727a",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index e69de29..08d2bf5 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -0,0 +1 @@",
+ "+typeof x;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ab63e3750b2f4626e4ffc50908102e9f02920950"
+ "shas": "38dbecd6735244d4c2c50c6608e64fd7df72b900..408a6dcf89d854252ec12de52f008a2a88793ade"
}
,{
"testCaseDescription": "javascript-type-operator-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "ab63e3750b2f4626e4ffc50908102e9f02920950",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index 08d2bf5..8b9c2f4 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1 +1,3 @@",
+ "+x instanceof String;",
+ "+typeof x;",
+ " typeof x;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "800baf212ebe5767adc73a88b842034f247998a9"
+ "shas": "408a6dcf89d854252ec12de52f008a2a88793ade..50475853b794903dd58705a2648d465fa42db1c1"
}
,{
"testCaseDescription": "javascript-type-operator-delete-insert-test",
@@ -102,9 +118,19 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "800baf212ebe5767adc73a88b842034f247998a9",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index 8b9c2f4..6a5be18 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-x instanceof String;",
+ "+typeof x;",
+ " typeof x;",
+ " typeof x;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4e9b73c3d185e4b21436c8d3ff6487be0cdb7178"
+ "shas": "50475853b794903dd58705a2648d465fa42db1c1..033d2812882757f8235cbbc27a1059188d125636"
}
,{
"testCaseDescription": "javascript-type-operator-replacement-test",
@@ -133,9 +159,19 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "4e9b73c3d185e4b21436c8d3ff6487be0cdb7178",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index 6a5be18..8b9c2f4 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-typeof x;",
+ "+x instanceof String;",
+ " typeof x;",
+ " typeof x;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d92be6360746626cd309c6918c44ba101125e1f1"
+ "shas": "033d2812882757f8235cbbc27a1059188d125636..a6dcc28c9ae5225546c6829efd0ff16e42357fa3"
}
,{
"testCaseDescription": "javascript-type-operator-delete-replacement-test",
@@ -194,9 +230,19 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "d92be6360746626cd309c6918c44ba101125e1f1",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index 8b9c2f4..d438f9f 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-x instanceof String;",
+ "-typeof x;",
+ " typeof x;",
+ "+x instanceof String;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f9a253ac2748f9207579c7b5939635362743c03c"
+ "shas": "a6dcc28c9ae5225546c6829efd0ff16e42357fa3..bb1b06901faca6abda996edbee1901289e63abde"
}
,{
"testCaseDescription": "javascript-type-operator-delete-test",
@@ -225,9 +271,17 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "f9a253ac2748f9207579c7b5939635362743c03c",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index d438f9f..0bf5275 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1,2 +1 @@",
+ "-typeof x;",
+ " x instanceof String;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9074037314693fe2bfe8b91f4ae169843ad0c159"
+ "shas": "bb1b06901faca6abda996edbee1901289e63abde..bc73ac8dfd8a42fc942bd8dac8012ef2e3a217da"
}
,{
"testCaseDescription": "javascript-type-operator-delete-rest-test",
@@ -256,7 +310,14 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "9074037314693fe2bfe8b91f4ae169843ad0c159",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index 0bf5275..e69de29 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1 +0,0 @@",
+ "-x instanceof String;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "979a03e21696fd6d2f5ef3c8c8e7473810cfc7c9"
+ "shas": "bc73ac8dfd8a42fc942bd8dac8012ef2e3a217da..b5645de0a9c0002d8f44d302c200dd88ff113f52"
}]
diff --git a/test/corpus/diff-summaries/javascript/undefined.json b/test/corpus/diff-summaries/javascript/undefined.json
index d978c5fec..1e99c042f 100644
--- a/test/corpus/diff-summaries/javascript/undefined.json
+++ b/test/corpus/diff-summaries/javascript/undefined.json
@@ -25,9 +25,16 @@
"filePaths": [
"undefined.js"
],
- "sha1": "ed321b51c08d6640a37c2c75423bda8952ed1a3a",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index e69de29..c2ca02c 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -0,0 +1 @@",
+ "+undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a56b90728cebab77c395a98ec6ee0988a57b237c"
+ "shas": "9f36bd70533d2f145bb9661791f0ea760bf949d5..5ea4083212daf3e2a900de3b68508a604ade8596"
}
,{
"testCaseDescription": "javascript-undefined-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"undefined.js"
],
- "sha1": "a56b90728cebab77c395a98ec6ee0988a57b237c",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index c2ca02c..a4352cc 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1 +1,3 @@",
+ "+return undefined;",
+ "+undefined;",
+ " undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2773c4bb79f8e74eb53702692b6f46e7b660c328"
+ "shas": "5ea4083212daf3e2a900de3b68508a604ade8596..d6cc7e90bce713f04bcfee5d53e1a112b1bfad0a"
}
,{
"testCaseDescription": "javascript-undefined-delete-insert-test",
@@ -117,9 +133,19 @@
"filePaths": [
"undefined.js"
],
- "sha1": "2773c4bb79f8e74eb53702692b6f46e7b660c328",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index a4352cc..52ea257 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1,3 +1,3 @@",
+ "-return undefined;",
+ "+undefined;",
+ " undefined;",
+ " undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1e98da533e19013215fa8caa3cbced7d0ea7eeb0"
+ "shas": "d6cc7e90bce713f04bcfee5d53e1a112b1bfad0a..718b0c7d530a5e063201c119f59091b97d0e90d3"
}
,{
"testCaseDescription": "javascript-undefined-replacement-test",
@@ -163,9 +189,19 @@
"filePaths": [
"undefined.js"
],
- "sha1": "1e98da533e19013215fa8caa3cbced7d0ea7eeb0",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index 52ea257..a4352cc 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1,3 +1,3 @@",
+ "-undefined;",
+ "+return undefined;",
+ " undefined;",
+ " undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f485b80ad884f1a5f0311152cfafd67c11b27a78"
+ "shas": "718b0c7d530a5e063201c119f59091b97d0e90d3..829fc4f00b66a91b67b0d0d41023f3d48fb34aa8"
}
,{
"testCaseDescription": "javascript-undefined-delete-replacement-test",
@@ -224,9 +260,19 @@
"filePaths": [
"undefined.js"
],
- "sha1": "f485b80ad884f1a5f0311152cfafd67c11b27a78",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index a4352cc..a16e747 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1,3 +1,2 @@",
+ "-return undefined;",
+ "-undefined;",
+ " undefined;",
+ "+return undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a876b838a04ca6202abc213d44015f573369c28a"
+ "shas": "829fc4f00b66a91b67b0d0d41023f3d48fb34aa8..ca6a3d94c002135dcd0d1096f808eadb016c1adf"
}
,{
"testCaseDescription": "javascript-undefined-delete-test",
@@ -255,9 +301,17 @@
"filePaths": [
"undefined.js"
],
- "sha1": "a876b838a04ca6202abc213d44015f573369c28a",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index a16e747..fb505bb 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1,2 +1 @@",
+ "-undefined;",
+ " return undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "773d4180add43986cc8c54b6dbfe8bff9fd3a7b3"
+ "shas": "ca6a3d94c002135dcd0d1096f808eadb016c1adf..2952f11c8fb57194cae4acde26f39231327790b0"
}
,{
"testCaseDescription": "javascript-undefined-delete-rest-test",
@@ -286,7 +340,14 @@
"filePaths": [
"undefined.js"
],
- "sha1": "773d4180add43986cc8c54b6dbfe8bff9fd3a7b3",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index fb505bb..e69de29 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1 +0,0 @@",
+ "-return undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fc80ccb71b0c0f159f05f8232853473f7f64457e"
+ "shas": "2952f11c8fb57194cae4acde26f39231327790b0..bc804312603351b07d0e242d9b3675d646934512"
}]
diff --git a/test/corpus/diff-summaries/javascript/var-declaration.json b/test/corpus/diff-summaries/javascript/var-declaration.json
index 88bea25e1..3840b00b0 100644
--- a/test/corpus/diff-summaries/javascript/var-declaration.json
+++ b/test/corpus/diff-summaries/javascript/var-declaration.json
@@ -25,9 +25,16 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "53a957ef4eb59591aa292324c9d8a45e7b4ef059",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index e69de29..b506100 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -0,0 +1 @@",
+ "+var x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "eca8f41092ecc12fb3d8a50342b0da453975caa1"
+ "shas": "5d2db352ed0e33bb51a7f2330066274984490127..f455ffd086c07cb3e4de74f4da0be7e944d063f7"
}
,{
"testCaseDescription": "javascript-var-declaration-replacement-insert-test",
@@ -101,9 +108,18 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "eca8f41092ecc12fb3d8a50342b0da453975caa1",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index b506100..b08ebfb 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1 +1,3 @@",
+ "+var x, y = {}, z;",
+ "+var x = 1;",
+ " var x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a706f998915f3f6d14c568b63c2c0bc0a83115d4"
+ "shas": "f455ffd086c07cb3e4de74f4da0be7e944d063f7..7c7c53ef609ab1a3f9dd578a6e7b3af487d1a8d6"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-insert-test",
@@ -177,9 +193,19 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "a706f998915f3f6d14c568b63c2c0bc0a83115d4",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index b08ebfb..adc261e 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1,3 +1,3 @@",
+ "-var x, y = {}, z;",
+ "+var x = 1;",
+ " var x = 1;",
+ " var x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9291790399d68cd679b339bffce499124ef3556d"
+ "shas": "7c7c53ef609ab1a3f9dd578a6e7b3af487d1a8d6..8c51fa18b7b49a6bb22947979e3660da861b8472"
}
,{
"testCaseDescription": "javascript-var-declaration-replacement-test",
@@ -250,9 +276,19 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "9291790399d68cd679b339bffce499124ef3556d",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index adc261e..b08ebfb 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1,3 +1,3 @@",
+ "-var x = 1;",
+ "+var x, y = {}, z;",
+ " var x = 1;",
+ " var x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4cddf496e69dd6e9b82c113448d8b304ef06befe"
+ "shas": "8c51fa18b7b49a6bb22947979e3660da861b8472..41c866c677aca04b21b600e74d218ccc998d2f5d"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-replacement-test",
@@ -371,9 +407,19 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "4cddf496e69dd6e9b82c113448d8b304ef06befe",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index b08ebfb..514f7c4 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1,3 +1,2 @@",
+ "-var x, y = {}, z;",
+ "-var x = 1;",
+ " var x = 1;",
+ "+var x, y = {}, z;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0e2767a5025c5f200613f4355ffc30f7fc52b04a"
+ "shas": "41c866c677aca04b21b600e74d218ccc998d2f5d..4330d72069a0ee02f257a7a2958054b36255ea3a"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-test",
@@ -402,9 +448,17 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "0e2767a5025c5f200613f4355ffc30f7fc52b04a",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index 514f7c4..9fc69e2 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1,2 +1 @@",
+ "-var x = 1;",
+ " var x, y = {}, z;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6ac202ddaa40892f710109a8877210e45cfec3e8"
+ "shas": "4330d72069a0ee02f257a7a2958054b36255ea3a..2285435873a4dd3e309e0a9950307823b9f95795"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-rest-test",
@@ -463,7 +517,14 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "6ac202ddaa40892f710109a8877210e45cfec3e8",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index 9fc69e2..e69de29 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1 +0,0 @@",
+ "-var x, y = {}, z;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "51cb9277c2233716e2f002c08a23656f70425838"
+ "shas": "2285435873a4dd3e309e0a9950307823b9f95795..81bc4513ad3979452e9e95586a5fbc9ca66eeadc"
}]
diff --git a/test/corpus/diff-summaries/javascript/variable.json b/test/corpus/diff-summaries/javascript/variable.json
index 42ded2125..543761464 100644
--- a/test/corpus/diff-summaries/javascript/variable.json
+++ b/test/corpus/diff-summaries/javascript/variable.json
@@ -25,9 +25,16 @@
"filePaths": [
"variable.js"
],
- "sha1": "e3169a584f82eaedeb405338ea6175466369ab58",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index e69de29..1cf4ad0 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -0,0 +1 @@",
+ "+theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1a55e497310765aeaf9588f96be0e09db3e412d3"
+ "shas": "2e348ee88f62c0857d6f6ce2ab3ee0d46f12afeb..09aa9131842b754fdd19963205e4e00f4413871b"
}
,{
"testCaseDescription": "javascript-variable-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"variable.js"
],
- "sha1": "1a55e497310765aeaf9588f96be0e09db3e412d3",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index 1cf4ad0..888855a 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1 +1,3 @@",
+ "+theVar2",
+ "+theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b137a7ba93647db3debc5e5acc727ff5532534e6"
+ "shas": "09aa9131842b754fdd19963205e4e00f4413871b..0b3b0533e575b679bbba53387580ba2c730806e4"
}
,{
"testCaseDescription": "javascript-variable-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"variable.js"
],
- "sha1": "b137a7ba93647db3debc5e5acc727ff5532534e6",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index 888855a..60e041c 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1,3 +1,3 @@",
+ "-theVar2",
+ "+theVar;",
+ " theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "55e6455cba1db43bd4ddbdc05e0f702dabad4fc6"
+ "shas": "0b3b0533e575b679bbba53387580ba2c730806e4..03875ee2891e9d8081f5d4bace0acb59724eca90"
}
,{
"testCaseDescription": "javascript-variable-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"variable.js"
],
- "sha1": "55e6455cba1db43bd4ddbdc05e0f702dabad4fc6",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index 60e041c..888855a 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1,3 +1,3 @@",
+ "-theVar;",
+ "+theVar2",
+ " theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7ddc9d4ba3ac1b29020686991372ac5b08e39e28"
+ "shas": "03875ee2891e9d8081f5d4bace0acb59724eca90..fc9c0d118d51bb745bf3665c575c58592deee4d5"
}
,{
"testCaseDescription": "javascript-variable-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"variable.js"
],
- "sha1": "7ddc9d4ba3ac1b29020686991372ac5b08e39e28",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index 888855a..fbc7b28 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1,3 +1,2 @@",
+ "-theVar2",
+ "-theVar;",
+ " theVar;",
+ "+theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7a50cf3b307f904daddfd9be499657b702288b55"
+ "shas": "fc9c0d118d51bb745bf3665c575c58592deee4d5..e286370e12767dd248982f92fd5f058e1099616e"
}
,{
"testCaseDescription": "javascript-variable-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"variable.js"
],
- "sha1": "7a50cf3b307f904daddfd9be499657b702288b55",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index fbc7b28..7276d95 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1,2 +1 @@",
+ "-theVar;",
+ " theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "064e39f36f22820c30ef0a7a9f5571c3ca7df914"
+ "shas": "e286370e12767dd248982f92fd5f058e1099616e..841c185fa272c7e634d52eca4fd38d05c1ac72a4"
}
,{
"testCaseDescription": "javascript-variable-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"variable.js"
],
- "sha1": "064e39f36f22820c30ef0a7a9f5571c3ca7df914",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index 7276d95..e69de29 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1 +0,0 @@",
+ "-theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e0e3afdc072a442646b858257a8842112c729449"
+ "shas": "841c185fa272c7e634d52eca4fd38d05c1ac72a4..2642fef686808ac2a6c5edde323e87257f4f2983"
}]
diff --git a/test/corpus/diff-summaries/javascript/void-operator.json b/test/corpus/diff-summaries/javascript/void-operator.json
index 28c30ee09..5bcbc9d50 100644
--- a/test/corpus/diff-summaries/javascript/void-operator.json
+++ b/test/corpus/diff-summaries/javascript/void-operator.json
@@ -25,9 +25,16 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "003fa853280eb9156b63626be54039b1bc67ea49",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index e69de29..02aa750 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -0,0 +1 @@",
+ "+void b()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b2a1d90970aad3b17a32296c808fc304c993030f"
+ "shas": "56f88d5286e94da2b11b7f6d0a35aa836d4f5921..090251ad4b6d167fb4a8ada452c235f6ef453446"
}
,{
"testCaseDescription": "javascript-void-operator-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "b2a1d90970aad3b17a32296c808fc304c993030f",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index 02aa750..c493dc5 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1 +1,3 @@",
+ "+void c()",
+ "+void b()",
+ " void b()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "08e1a511413f6784d8362345303effd525ace612"
+ "shas": "090251ad4b6d167fb4a8ada452c235f6ef453446..bf6411aac8dfb3eeb0f991114c7f48b390b61430"
}
,{
"testCaseDescription": "javascript-void-operator-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "08e1a511413f6784d8362345303effd525ace612",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index c493dc5..aae2f63 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-void c()",
+ "+void b()",
+ " void b()",
+ " void b()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "61c3dc82324f2c3cf7fbb6dd3920ea8108eac065"
+ "shas": "bf6411aac8dfb3eeb0f991114c7f48b390b61430..d00f222abddf5191477b57afc4101cf73ee16ec5"
}
,{
"testCaseDescription": "javascript-void-operator-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "61c3dc82324f2c3cf7fbb6dd3920ea8108eac065",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index aae2f63..c493dc5 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-void b()",
+ "+void c()",
+ " void b()",
+ " void b()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fb72e23298e5a43c2f52f7f5142d97cdd239deed"
+ "shas": "d00f222abddf5191477b57afc4101cf73ee16ec5..36271b63277a1739ae109605f2f520baf14525b4"
}
,{
"testCaseDescription": "javascript-void-operator-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "fb72e23298e5a43c2f52f7f5142d97cdd239deed",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index c493dc5..738c34a 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-void c()",
+ "-void b()",
+ " void b()",
+ "+void c()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1390d7a8c382726e53b6bcc64d16fd1cd64c4640"
+ "shas": "36271b63277a1739ae109605f2f520baf14525b4..350bf156c704fb4f26d0ada86678e654d40d70cc"
}
,{
"testCaseDescription": "javascript-void-operator-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "1390d7a8c382726e53b6bcc64d16fd1cd64c4640",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index 738c34a..8e9ceba 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1,2 +1 @@",
+ "-void b()",
+ " void c()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4721ce39fec97805d942cd64afcea61034f0c011"
+ "shas": "350bf156c704fb4f26d0ada86678e654d40d70cc..684600d4371b29448fa610da1a5e4d2d7710c3aa"
}
,{
"testCaseDescription": "javascript-void-operator-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "4721ce39fec97805d942cd64afcea61034f0c011",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index 8e9ceba..e69de29 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1 +0,0 @@",
+ "-void c()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "cf3bb492593b241390a7cfd11dbdbd3d251a4177"
+ "shas": "684600d4371b29448fa610da1a5e4d2d7710c3aa..5da04c6d20aa6fdedbc205bf855829ccd10687f3"
}]
diff --git a/test/corpus/diff-summaries/javascript/while-statement.json b/test/corpus/diff-summaries/javascript/while-statement.json
index 870467318..03a6ebc0f 100644
--- a/test/corpus/diff-summaries/javascript/while-statement.json
+++ b/test/corpus/diff-summaries/javascript/while-statement.json
@@ -25,9 +25,16 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "a155a2bd652ca5aaa95ea8e31c7eac9662aa07f9",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index e69de29..1ea2800 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -0,0 +1 @@",
+ "+while (a) { b(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "97cc8bda4de00f4a8770d024d5ffb43af88a91c3"
+ "shas": "0b1a50d075cdb5202c523f929502c24a9fce63ce..db921ea9f999f72cb6399c64092e4b0904628ff8"
}
,{
"testCaseDescription": "javascript-while-statement-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "97cc8bda4de00f4a8770d024d5ffb43af88a91c3",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index 1ea2800..c322323 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1 +1,3 @@",
+ "+while (b) { a(); };",
+ "+while (a) { b(); };",
+ " while (a) { b(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "47dfc4d4ccd3bc0f418576938c0a5501b54e00fe"
+ "shas": "db921ea9f999f72cb6399c64092e4b0904628ff8..daa66677bfa5359e0679879da34e3ee1bed674a6"
}
,{
"testCaseDescription": "javascript-while-statement-delete-insert-test",
@@ -141,9 +157,19 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "47dfc4d4ccd3bc0f418576938c0a5501b54e00fe",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index c322323..ea96716 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-while (b) { a(); };",
+ "+while (a) { b(); };",
+ " while (a) { b(); };",
+ " while (a) { b(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "07111f9c087018d34f8c7564fb7683008f00559b"
+ "shas": "daa66677bfa5359e0679879da34e3ee1bed674a6..24da8276225fa14bdffd90de951fc90cd18759ed"
}
,{
"testCaseDescription": "javascript-while-statement-replacement-test",
@@ -211,9 +237,19 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "07111f9c087018d34f8c7564fb7683008f00559b",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index ea96716..c322323 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-while (a) { b(); };",
+ "+while (b) { a(); };",
+ " while (a) { b(); };",
+ " while (a) { b(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a2e6488177df310b5938eb448488bee2eaf4c24e"
+ "shas": "24da8276225fa14bdffd90de951fc90cd18759ed..cae263f93a9ddcbed5411b06251f41d4da9c07d4"
}
,{
"testCaseDescription": "javascript-while-statement-delete-replacement-test",
@@ -272,9 +308,19 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "a2e6488177df310b5938eb448488bee2eaf4c24e",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index c322323..28f4b21 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-while (b) { a(); };",
+ "-while (a) { b(); };",
+ " while (a) { b(); };",
+ "+while (b) { a(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9b3f1334351b7de4a7e34b42c4c1e001e4bf2744"
+ "shas": "cae263f93a9ddcbed5411b06251f41d4da9c07d4..09f8c3d79b360939277158f185f0e13ecbecdd11"
}
,{
"testCaseDescription": "javascript-while-statement-delete-test",
@@ -303,9 +349,17 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "9b3f1334351b7de4a7e34b42c4c1e001e4bf2744",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index 28f4b21..e185b25 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1,2 +1 @@",
+ "-while (a) { b(); };",
+ " while (b) { a(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d942929671d3c1ebf83ab87803047e8aceb1c837"
+ "shas": "09f8c3d79b360939277158f185f0e13ecbecdd11..11144cc015f5698c8473a6efd76c3129422cf2a2"
}
,{
"testCaseDescription": "javascript-while-statement-delete-rest-test",
@@ -334,7 +388,14 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "d942929671d3c1ebf83ab87803047e8aceb1c837",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index e185b25..e69de29 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1 +0,0 @@",
+ "-while (b) { a(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ec8ba8297edb4d6d8dbc00d6f028116e0b58abe8"
+ "shas": "11144cc015f5698c8473a6efd76c3129422cf2a2..cd322134775da8db98f5a151ec8e2f5d9eddd3cf"
}]
diff --git a/test/corpus/diff-summaries/ruby/and-or.json b/test/corpus/diff-summaries/ruby/and-or.json
index 4f8779073..3f555ae25 100644
--- a/test/corpus/diff-summaries/ruby/and-or.json
+++ b/test/corpus/diff-summaries/ruby/and-or.json
@@ -25,9 +25,16 @@
"filePaths": [
"and-or.rb"
],
- "sha1": "f9e62bf41467cae8ada35780dd97dbbbddf57da5",
+ "patch": [
+ "diff --git a/and-or.rb b/and-or.rb",
+ "index e69de29..8e828c0 100644",
+ "--- a/and-or.rb",
+ "+++ b/and-or.rb",
+ "@@ -0,0 +1 @@",
+ "+foo and bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "3dbda12dac387b0d37ca78e7f01809e8f3e7a39b"
+ "shas": "c7d3f438c72d2ab2a09e3fa47ba1cf9b175d2a9b..0bc5f86f8c781f501003b94889818004364037b9"
}
,{
"testCaseDescription": "ruby-and-or-replacement-insert-test",
@@ -86,9 +93,19 @@
"filePaths": [
"and-or.rb"
],
- "sha1": "3dbda12dac387b0d37ca78e7f01809e8f3e7a39b",
+ "patch": [
+ "diff --git a/and-or.rb b/and-or.rb",
+ "index 8e828c0..fe52247 100644",
+ "--- a/and-or.rb",
+ "+++ b/and-or.rb",
+ "@@ -1 +1,4 @@",
+ "+foo or bar",
+ "+a or b and c",
+ "+foo and bar",
+ " foo and bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e28ff49e1a934201eb081645ddbbd5983b7cff3e"
+ "shas": "0bc5f86f8c781f501003b94889818004364037b9..2c06275827cfa3bbaada5117072cd19574d8d7a9"
}
,{
"testCaseDescription": "ruby-and-or-delete-insert-test",
@@ -117,9 +134,20 @@
"filePaths": [
"and-or.rb"
],
- "sha1": "e28ff49e1a934201eb081645ddbbd5983b7cff3e",
+ "patch": [
+ "diff --git a/and-or.rb b/and-or.rb",
+ "index fe52247..b09c067 100644",
+ "--- a/and-or.rb",
+ "+++ b/and-or.rb",
+ "@@ -1,4 +1,3 @@",
+ "-foo or bar",
+ "-a or b and c",
+ "+foo and bar",
+ " foo and bar",
+ " foo and bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "c3983115a7ed26e52980b39fbb57d1f26a31e1fe"
+ "shas": "2c06275827cfa3bbaada5117072cd19574d8d7a9..e800a12b636011a03bc99b86835317cd7ad3ecd1"
}
,{
"testCaseDescription": "ruby-and-or-replacement-test",
@@ -148,9 +176,20 @@
"filePaths": [
"and-or.rb"
],
- "sha1": "c3983115a7ed26e52980b39fbb57d1f26a31e1fe",
+ "patch": [
+ "diff --git a/and-or.rb b/and-or.rb",
+ "index b09c067..fe52247 100644",
+ "--- a/and-or.rb",
+ "+++ b/and-or.rb",
+ "@@ -1,3 +1,4 @@",
+ "-foo and bar",
+ "+foo or bar",
+ "+a or b and c",
+ " foo and bar",
+ " foo and bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "f6e7e8cee1becdcc3ecfb253d5004399b90c7638"
+ "shas": "e800a12b636011a03bc99b86835317cd7ad3ecd1..c9340cbb8ada35c896fa285761dd0e9dac96fd0b"
}
,{
"testCaseDescription": "ruby-and-or-delete-replacement-test",
@@ -209,9 +248,20 @@
"filePaths": [
"and-or.rb"
],
- "sha1": "f6e7e8cee1becdcc3ecfb253d5004399b90c7638",
+ "patch": [
+ "diff --git a/and-or.rb b/and-or.rb",
+ "index fe52247..a621325 100644",
+ "--- a/and-or.rb",
+ "+++ b/and-or.rb",
+ "@@ -1,4 +1,3 @@",
+ "+foo and bar",
+ " foo or bar",
+ " a or b and c",
+ "-foo and bar",
+ "-foo and bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "a31ed69713710a876f50a672b66f36a10b49a681"
+ "shas": "c9340cbb8ada35c896fa285761dd0e9dac96fd0b..66224b27113350bc8e9d7ffddc2fe22fee05baa2"
}
,{
"testCaseDescription": "ruby-and-or-delete-test",
@@ -240,9 +290,18 @@
"filePaths": [
"and-or.rb"
],
- "sha1": "a31ed69713710a876f50a672b66f36a10b49a681",
+ "patch": [
+ "diff --git a/and-or.rb b/and-or.rb",
+ "index a621325..d2060f6 100644",
+ "--- a/and-or.rb",
+ "+++ b/and-or.rb",
+ "@@ -1,3 +1,2 @@",
+ "-foo and bar",
+ " foo or bar",
+ " a or b and c"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "d9e002237b1f453c85a84df06bc86a871b453d97"
+ "shas": "66224b27113350bc8e9d7ffddc2fe22fee05baa2..22157102e33b0c6c91eed738c3c7a3ce0edc3fa7"
}
,{
"testCaseDescription": "ruby-and-or-delete-rest-test",
@@ -286,7 +345,15 @@
"filePaths": [
"and-or.rb"
],
- "sha1": "d9e002237b1f453c85a84df06bc86a871b453d97",
+ "patch": [
+ "diff --git a/and-or.rb b/and-or.rb",
+ "index d2060f6..e69de29 100644",
+ "--- a/and-or.rb",
+ "+++ b/and-or.rb",
+ "@@ -1,2 +0,0 @@",
+ "-foo or bar",
+ "-a or b and c"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e9bfaab31e3a83e3c8e8d890bd8e2a6cf1f5a529"
+ "shas": "22157102e33b0c6c91eed738c3c7a3ce0edc3fa7..956b136e24f76c977fefd27d5368ecd527f721ec"
}]
diff --git a/test/corpus/diff-summaries/ruby/array.json b/test/corpus/diff-summaries/ruby/array.json
index 1be480c12..279a9c36f 100644
--- a/test/corpus/diff-summaries/ruby/array.json
+++ b/test/corpus/diff-summaries/ruby/array.json
@@ -25,9 +25,16 @@
"filePaths": [
"array.rb"
],
- "sha1": "275c429c547953450d7c9bf531188b8f50e9295d",
+ "patch": [
+ "diff --git a/array.rb b/array.rb",
+ "index e69de29..a900520 100644",
+ "--- a/array.rb",
+ "+++ b/array.rb",
+ "@@ -0,0 +1 @@",
+ "+[ 1, 2, 3]"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "99a499d6d76ebb87c352c0122896b9002068a2fb"
+ "shas": "e8c4c9b4ba151237a0e88d5a650d34ee5a5a1b61..92505afbaea485d23aecf7f8edb66dfad7e17fd8"
}
,{
"testCaseDescription": "ruby-array-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"array.rb"
],
- "sha1": "99a499d6d76ebb87c352c0122896b9002068a2fb",
+ "patch": [
+ "diff --git a/array.rb b/array.rb",
+ "index a900520..c3ae0a1 100644",
+ "--- a/array.rb",
+ "+++ b/array.rb",
+ "@@ -1 +1,3 @@",
+ "+['a', 'b', 'c']",
+ "+[ 1, 2, 3]",
+ " [ 1, 2, 3]"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "cf7716725c52e82855702ff87f2bc53c829fbda9"
+ "shas": "92505afbaea485d23aecf7f8edb66dfad7e17fd8..4f3473df5291027b89f3b4fe9ca1854e49454cc4"
}
,{
"testCaseDescription": "ruby-array-delete-insert-test",
@@ -177,9 +193,19 @@
"filePaths": [
"array.rb"
],
- "sha1": "cf7716725c52e82855702ff87f2bc53c829fbda9",
+ "patch": [
+ "diff --git a/array.rb b/array.rb",
+ "index c3ae0a1..9d0ec26 100644",
+ "--- a/array.rb",
+ "+++ b/array.rb",
+ "@@ -1,3 +1,3 @@",
+ "-['a', 'b', 'c']",
+ "+[ 1, 2, 3]",
+ " [ 1, 2, 3]",
+ " [ 1, 2, 3]"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "2f4a0901ef95870d066861b89bfc388a446cfc81"
+ "shas": "4f3473df5291027b89f3b4fe9ca1854e49454cc4..9def16756eb5f54b2e6b55b6a4cdfeb4a8d5de46"
}
,{
"testCaseDescription": "ruby-array-replacement-test",
@@ -283,9 +309,19 @@
"filePaths": [
"array.rb"
],
- "sha1": "2f4a0901ef95870d066861b89bfc388a446cfc81",
+ "patch": [
+ "diff --git a/array.rb b/array.rb",
+ "index 9d0ec26..c3ae0a1 100644",
+ "--- a/array.rb",
+ "+++ b/array.rb",
+ "@@ -1,3 +1,3 @@",
+ "-[ 1, 2, 3]",
+ "+['a', 'b', 'c']",
+ " [ 1, 2, 3]",
+ " [ 1, 2, 3]"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "fed9d441befcfe8fce50601b0de754f6e0f25a97"
+ "shas": "9def16756eb5f54b2e6b55b6a4cdfeb4a8d5de46..201d96f51f94a1a40acc9278b6adc775bea84b0f"
}
,{
"testCaseDescription": "ruby-array-delete-replacement-test",
@@ -344,9 +380,19 @@
"filePaths": [
"array.rb"
],
- "sha1": "fed9d441befcfe8fce50601b0de754f6e0f25a97",
+ "patch": [
+ "diff --git a/array.rb b/array.rb",
+ "index c3ae0a1..102a972 100644",
+ "--- a/array.rb",
+ "+++ b/array.rb",
+ "@@ -1,3 +1,2 @@",
+ "-['a', 'b', 'c']",
+ "-[ 1, 2, 3]",
+ " [ 1, 2, 3]",
+ "+['a', 'b', 'c']"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "ff8e5cccb9751457edac3562f326432d9b6431ea"
+ "shas": "201d96f51f94a1a40acc9278b6adc775bea84b0f..b5284048ab1c80b398b60b7c632c733adde8df2e"
}
,{
"testCaseDescription": "ruby-array-delete-test",
@@ -375,9 +421,17 @@
"filePaths": [
"array.rb"
],
- "sha1": "ff8e5cccb9751457edac3562f326432d9b6431ea",
+ "patch": [
+ "diff --git a/array.rb b/array.rb",
+ "index 102a972..939152e 100644",
+ "--- a/array.rb",
+ "+++ b/array.rb",
+ "@@ -1,2 +1 @@",
+ "-[ 1, 2, 3]",
+ " ['a', 'b', 'c']"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "f085923cdf14b732c4e606edb4a13d463ca3633a"
+ "shas": "b5284048ab1c80b398b60b7c632c733adde8df2e..aff7086bf8fd3b7fc3be8f3bd49c41c46a049729"
}
,{
"testCaseDescription": "ruby-array-delete-rest-test",
@@ -406,7 +460,14 @@
"filePaths": [
"array.rb"
],
- "sha1": "f085923cdf14b732c4e606edb4a13d463ca3633a",
+ "patch": [
+ "diff --git a/array.rb b/array.rb",
+ "index 939152e..e69de29 100644",
+ "--- a/array.rb",
+ "+++ b/array.rb",
+ "@@ -1 +0,0 @@",
+ "-['a', 'b', 'c']"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "fb977a1a932fedffdf11b59b7039edfee929898b"
+ "shas": "aff7086bf8fd3b7fc3be8f3bd49c41c46a049729..79b196cace027a076f4ba235171fd4f409bdaba9"
}]
diff --git a/test/corpus/diff-summaries/ruby/assignment.json b/test/corpus/diff-summaries/ruby/assignment.json
index 528139d68..b6905929e 100644
--- a/test/corpus/diff-summaries/ruby/assignment.json
+++ b/test/corpus/diff-summaries/ruby/assignment.json
@@ -25,9 +25,16 @@
"filePaths": [
"assignment.rb"
],
- "sha1": "c1011bb99d1909091258a822b4b1cffd554404e2",
+ "patch": [
+ "diff --git a/assignment.rb b/assignment.rb",
+ "index e69de29..3aea0c5 100644",
+ "--- a/assignment.rb",
+ "+++ b/assignment.rb",
+ "@@ -0,0 +1 @@",
+ "+x = 0"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e41b3065504363a0301c9b303287647996485eb0"
+ "shas": "4d0ef41f7debeacebe9a218e39bb2b48c8405446..ad5a90e438df179af24b1db62954dd57456ecb70"
}
,{
"testCaseDescription": "ruby-assignment-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"assignment.rb"
],
- "sha1": "e41b3065504363a0301c9b303287647996485eb0",
+ "patch": [
+ "diff --git a/assignment.rb b/assignment.rb",
+ "index 3aea0c5..80ff640 100644",
+ "--- a/assignment.rb",
+ "+++ b/assignment.rb",
+ "@@ -1 +1,3 @@",
+ "+x = 1",
+ "+x = 0",
+ " x = 0"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "8f67f0dddc276771748784c1c867ba26ef19cda7"
+ "shas": "ad5a90e438df179af24b1db62954dd57456ecb70..91faac962a01a884edd6ada891ced7040d038ad4"
}
,{
"testCaseDescription": "ruby-assignment-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"assignment.rb"
],
- "sha1": "8f67f0dddc276771748784c1c867ba26ef19cda7",
+ "patch": [
+ "diff --git a/assignment.rb b/assignment.rb",
+ "index 80ff640..e9580bc 100644",
+ "--- a/assignment.rb",
+ "+++ b/assignment.rb",
+ "@@ -1,3 +1,3 @@",
+ "-x = 1",
+ "+x = 0",
+ " x = 0",
+ " x = 0"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "68f0d646d1b49e7e5b49f56b3af54223fb47c85a"
+ "shas": "91faac962a01a884edd6ada891ced7040d038ad4..9176406da7e16de7c17eddfbeb557a7441dcae6b"
}
,{
"testCaseDescription": "ruby-assignment-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"assignment.rb"
],
- "sha1": "68f0d646d1b49e7e5b49f56b3af54223fb47c85a",
+ "patch": [
+ "diff --git a/assignment.rb b/assignment.rb",
+ "index e9580bc..80ff640 100644",
+ "--- a/assignment.rb",
+ "+++ b/assignment.rb",
+ "@@ -1,3 +1,3 @@",
+ "-x = 0",
+ "+x = 1",
+ " x = 0",
+ " x = 0"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "26627cf899d8f7bc331270249d6a9333e048ac19"
+ "shas": "9176406da7e16de7c17eddfbeb557a7441dcae6b..781f04eca397646ee7614b9206aa7eff79a2e400"
}
,{
"testCaseDescription": "ruby-assignment-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"assignment.rb"
],
- "sha1": "26627cf899d8f7bc331270249d6a9333e048ac19",
+ "patch": [
+ "diff --git a/assignment.rb b/assignment.rb",
+ "index 80ff640..2465cb3 100644",
+ "--- a/assignment.rb",
+ "+++ b/assignment.rb",
+ "@@ -1,3 +1,2 @@",
+ "-x = 1",
+ "-x = 0",
+ " x = 0",
+ "+x = 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "b4bd50ed246f8e68c1a7f3e24e78ceb4e65c96f6"
+ "shas": "781f04eca397646ee7614b9206aa7eff79a2e400..75bccc3232c4b4773225c70ba35b08ba08e95d38"
}
,{
"testCaseDescription": "ruby-assignment-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"assignment.rb"
],
- "sha1": "b4bd50ed246f8e68c1a7f3e24e78ceb4e65c96f6",
+ "patch": [
+ "diff --git a/assignment.rb b/assignment.rb",
+ "index 2465cb3..7d4290a 100644",
+ "--- a/assignment.rb",
+ "+++ b/assignment.rb",
+ "@@ -1,2 +1 @@",
+ "-x = 0",
+ " x = 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "9fe03a3aec3859d5b48075e09fb5024bfd82c375"
+ "shas": "75bccc3232c4b4773225c70ba35b08ba08e95d38..5dd9958c7bc7d5736ba816f77ce0a88f7b2fa709"
}
,{
"testCaseDescription": "ruby-assignment-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"assignment.rb"
],
- "sha1": "9fe03a3aec3859d5b48075e09fb5024bfd82c375",
+ "patch": [
+ "diff --git a/assignment.rb b/assignment.rb",
+ "index 7d4290a..e69de29 100644",
+ "--- a/assignment.rb",
+ "+++ b/assignment.rb",
+ "@@ -1 +0,0 @@",
+ "-x = 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "9e7143591420559db8bb6c8648077d460d371b9f"
+ "shas": "5dd9958c7bc7d5736ba816f77ce0a88f7b2fa709..a07f2fef830bc79ffa2136025c4e29d5c8a0ff1b"
}]
diff --git a/test/corpus/diff-summaries/ruby/begin.json b/test/corpus/diff-summaries/ruby/begin.json
new file mode 100644
index 000000000..89beda515
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/begin.json
@@ -0,0 +1,244 @@
+[{
+ "testCaseDescription": "ruby-begin-setup-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index e69de29..ff7bbbe 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -0,0 +1,2 @@",
+ "+def foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "72e1f4912f54a936266422abbb53a9c2fc864992..d9be702e11b41377baa2f5fb3ccd4e3cf3dd81e4"
+}
+,{
+ "testCaseDescription": "ruby-begin-insert-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement in the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index ff7bbbe..7b4a3be 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -1,2 +1,4 @@",
+ " def foo",
+ "+begin",
+ "+end",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d9be702e11b41377baa2f5fb3ccd4e3cf3dd81e4..1f7c992ecbf8dc5434ec7da2bc396e814e91adc9"
+}
+,{
+ "testCaseDescription": "ruby-begin-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'puts('hi')' function call in a begin statement of the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index 7b4a3be..7879e55 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -1,4 +1,5 @@",
+ " def foo",
+ " begin",
+ "+ puts 'hi'",
+ " end",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1f7c992ecbf8dc5434ec7da2bc396e814e91adc9..a72bbedc16a6b300edf51b665ebaf90e62662ab8"
+}
+,{
+ "testCaseDescription": "ruby-begin-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the 'puts('hi')' function call in a begin statement of the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index 7879e55..7b4a3be 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -1,5 +1,4 @@",
+ " def foo",
+ " begin",
+ "- puts 'hi'",
+ " end",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "a72bbedc16a6b300edf51b665ebaf90e62662ab8..4ba57f34c39daab00f1b9fc48f1e162ced2e9a44"
+}
+,{
+ "testCaseDescription": "ruby-begin-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement in the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index 7b4a3be..ff7bbbe 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -1,4 +1,2 @@",
+ " def foo",
+ "-begin",
+ "-end",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "4ba57f34c39daab00f1b9fc48f1e162ced2e9a44..9995f52897de0441895de23887b80cd4c9b7ea75"
+}
+,{
+ "testCaseDescription": "ruby-begin-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index ff7bbbe..e69de29 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -1,2 +0,0 @@",
+ "-def foo",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "9995f52897de0441895de23887b80cd4c9b7ea75..cc81318f97e858789ab75eb6e9c4a9ef9a96807c"
+}]
diff --git a/test/corpus/diff-summaries/ruby/bitwise-operator.json b/test/corpus/diff-summaries/ruby/bitwise-operator.json
index 7b2ff6652..8508f6bda 100644
--- a/test/corpus/diff-summaries/ruby/bitwise-operator.json
+++ b/test/corpus/diff-summaries/ruby/bitwise-operator.json
@@ -55,9 +55,18 @@
"filePaths": [
"bitwise-operator.rb"
],
- "sha1": "85eb09d96abcd8b75415cc71358b6753031dd375",
+ "patch": [
+ "diff --git a/bitwise-operator.rb b/bitwise-operator.rb",
+ "index e69de29..a596f03 100644",
+ "--- a/bitwise-operator.rb",
+ "+++ b/bitwise-operator.rb",
+ "@@ -0,0 +1,3 @@",
+ "+a | b",
+ "+a >> b",
+ "+a ^ b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "f30cf572f929f8aa28b9722b1d241bdd3092d1cf"
+ "shas": "70d36a6a9817b1e91707c1f7f830a0568b959efa..ce65ef18e5032a270bbfcef7d593c68d270abaf4"
}
,{
"testCaseDescription": "ruby-bitwise-operator-replacement-insert-test",
@@ -146,9 +155,23 @@
"filePaths": [
"bitwise-operator.rb"
],
- "sha1": "f30cf572f929f8aa28b9722b1d241bdd3092d1cf",
+ "patch": [
+ "diff --git a/bitwise-operator.rb b/bitwise-operator.rb",
+ "index a596f03..826d98f 100644",
+ "--- a/bitwise-operator.rb",
+ "+++ b/bitwise-operator.rb",
+ "@@ -1,3 +1,8 @@",
+ "+a & b",
+ "+a << b",
+ "+a | b",
+ "+a >> b",
+ "+a ^ b",
+ " a | b",
+ " a >> b",
+ " a ^ b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "dc84e24a4de7c203974093883e81c2f9f7ed8dd8"
+ "shas": "ce65ef18e5032a270bbfcef7d593c68d270abaf4..3710a2840202f8625b9a440d8b556a6d30d2b6f6"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-insert-test",
@@ -177,9 +200,23 @@
"filePaths": [
"bitwise-operator.rb"
],
- "sha1": "dc84e24a4de7c203974093883e81c2f9f7ed8dd8",
+ "patch": [
+ "diff --git a/bitwise-operator.rb b/bitwise-operator.rb",
+ "index 826d98f..8f874fc 100644",
+ "--- a/bitwise-operator.rb",
+ "+++ b/bitwise-operator.rb",
+ "@@ -1,5 +1,6 @@",
+ "-a & b",
+ "-a << b",
+ "+a | b",
+ "+a >> b",
+ "+a ^ b",
+ " a | b",
+ " a >> b",
+ " a ^ b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "1313c16b9be2354df6c3222a09c150f838e6b632"
+ "shas": "3710a2840202f8625b9a440d8b556a6d30d2b6f6..88289eb5fde1222a010efda881ce7888c282fe61"
}
,{
"testCaseDescription": "ruby-bitwise-operator-replacement-test",
@@ -208,9 +245,23 @@
"filePaths": [
"bitwise-operator.rb"
],
- "sha1": "1313c16b9be2354df6c3222a09c150f838e6b632",
+ "patch": [
+ "diff --git a/bitwise-operator.rb b/bitwise-operator.rb",
+ "index 8f874fc..826d98f 100644",
+ "--- a/bitwise-operator.rb",
+ "+++ b/bitwise-operator.rb",
+ "@@ -1,6 +1,5 @@",
+ "-a | b",
+ "-a >> b",
+ "-a ^ b",
+ "+a & b",
+ "+a << b",
+ " a | b",
+ " a >> b",
+ " a ^ b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "8e70f2e4ce7b7f950d67bfbe677c92e25195437f"
+ "shas": "88289eb5fde1222a010efda881ce7888c282fe61..5ae589defd184d837cb3d384ab225f42299801d8"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-replacement-test",
@@ -269,9 +320,25 @@
"filePaths": [
"bitwise-operator.rb"
],
- "sha1": "8e70f2e4ce7b7f950d67bfbe677c92e25195437f",
+ "patch": [
+ "diff --git a/bitwise-operator.rb b/bitwise-operator.rb",
+ "index 826d98f..1a2a6da 100644",
+ "--- a/bitwise-operator.rb",
+ "+++ b/bitwise-operator.rb",
+ "@@ -1,8 +1,5 @@",
+ "-a & b",
+ "-a << b",
+ "-a | b",
+ "-a >> b",
+ "-a ^ b",
+ " a | b",
+ " a >> b",
+ " a ^ b",
+ "+a & b",
+ "+a << b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "9a6739d945526752e9ddf05b4bb315335a68a58d"
+ "shas": "5ae589defd184d837cb3d384ab225f42299801d8..29cf76ea1e49cdef2e616fed189fec268693ca87"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-test",
@@ -330,9 +397,20 @@
"filePaths": [
"bitwise-operator.rb"
],
- "sha1": "9a6739d945526752e9ddf05b4bb315335a68a58d",
+ "patch": [
+ "diff --git a/bitwise-operator.rb b/bitwise-operator.rb",
+ "index 1a2a6da..97e763b 100644",
+ "--- a/bitwise-operator.rb",
+ "+++ b/bitwise-operator.rb",
+ "@@ -1,5 +1,2 @@",
+ "-a | b",
+ "-a >> b",
+ "-a ^ b",
+ " a & b",
+ " a << b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "d1fb460ac12248c0351090d4be0d07b443afb5a3"
+ "shas": "29cf76ea1e49cdef2e616fed189fec268693ca87..4bb4fee464aeaf7f957b7750b0947e7c02f2a8a8"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-rest-test",
@@ -376,7 +454,15 @@
"filePaths": [
"bitwise-operator.rb"
],
- "sha1": "d1fb460ac12248c0351090d4be0d07b443afb5a3",
+ "patch": [
+ "diff --git a/bitwise-operator.rb b/bitwise-operator.rb",
+ "index 97e763b..e69de29 100644",
+ "--- a/bitwise-operator.rb",
+ "+++ b/bitwise-operator.rb",
+ "@@ -1,2 +0,0 @@",
+ "-a & b",
+ "-a << b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "c3ffed8011708e89709328349892066714996e97"
+ "shas": "4bb4fee464aeaf7f957b7750b0947e7c02f2a8a8..8b196e55798c1a5f125a87a869f770dca83665d6"
}]
diff --git a/test/corpus/diff-summaries/ruby/boolean-operator.json b/test/corpus/diff-summaries/ruby/boolean-operator.json
index 92dbc87dc..754aa298f 100644
--- a/test/corpus/diff-summaries/ruby/boolean-operator.json
+++ b/test/corpus/diff-summaries/ruby/boolean-operator.json
@@ -25,9 +25,16 @@
"filePaths": [
"boolean-operator.rb"
],
- "sha1": "0ba58b06e96f1b3ae8331ee4f06e4087a13c29f5",
+ "patch": [
+ "diff --git a/boolean-operator.rb b/boolean-operator.rb",
+ "index e69de29..ba0778d 100644",
+ "--- a/boolean-operator.rb",
+ "+++ b/boolean-operator.rb",
+ "@@ -0,0 +1 @@",
+ "+a || b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "9b569428d02cb0701d2c623c225c3781fe9bdb91"
+ "shas": "5b279526f66afb77b2588f5173ce44d7cc693f97..53ec9b4615b8872e47ba643814f579eb3d74ef32"
}
,{
"testCaseDescription": "ruby-boolean-operator-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"boolean-operator.rb"
],
- "sha1": "9b569428d02cb0701d2c623c225c3781fe9bdb91",
+ "patch": [
+ "diff --git a/boolean-operator.rb b/boolean-operator.rb",
+ "index ba0778d..2d34b94 100644",
+ "--- a/boolean-operator.rb",
+ "+++ b/boolean-operator.rb",
+ "@@ -1 +1,3 @@",
+ "+a && b",
+ "+a || b",
+ " a || b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "575bc50bf8b2ebcc1d460b20b850692116679c29"
+ "shas": "53ec9b4615b8872e47ba643814f579eb3d74ef32..02c804c5e37002a6843f3fc329c5db03ad4d51f6"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-insert-test",
@@ -84,9 +100,19 @@
"filePaths": [
"boolean-operator.rb"
],
- "sha1": "575bc50bf8b2ebcc1d460b20b850692116679c29",
+ "patch": [
+ "diff --git a/boolean-operator.rb b/boolean-operator.rb",
+ "index 2d34b94..2c61248 100644",
+ "--- a/boolean-operator.rb",
+ "+++ b/boolean-operator.rb",
+ "@@ -1,3 +1,3 @@",
+ "-a && b",
+ "+a || b",
+ " a || b",
+ " a || b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "6ffabd9c9ba3df0a98a4876fe1b8634d68355944"
+ "shas": "02c804c5e37002a6843f3fc329c5db03ad4d51f6..144d5b79b707781d8b5d1d56e281bcaa8598ae17"
}
,{
"testCaseDescription": "ruby-boolean-operator-replacement-test",
@@ -97,9 +123,19 @@
"filePaths": [
"boolean-operator.rb"
],
- "sha1": "6ffabd9c9ba3df0a98a4876fe1b8634d68355944",
+ "patch": [
+ "diff --git a/boolean-operator.rb b/boolean-operator.rb",
+ "index 2c61248..2d34b94 100644",
+ "--- a/boolean-operator.rb",
+ "+++ b/boolean-operator.rb",
+ "@@ -1,3 +1,3 @@",
+ "-a || b",
+ "+a && b",
+ " a || b",
+ " a || b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "2014ba4422d7597f91f3f3d412d29dce94e6f696"
+ "shas": "144d5b79b707781d8b5d1d56e281bcaa8598ae17..000c0198a566086df4d95a1ffd575748b7721552"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-replacement-test",
@@ -128,9 +164,19 @@
"filePaths": [
"boolean-operator.rb"
],
- "sha1": "2014ba4422d7597f91f3f3d412d29dce94e6f696",
+ "patch": [
+ "diff --git a/boolean-operator.rb b/boolean-operator.rb",
+ "index 2d34b94..32a41c9 100644",
+ "--- a/boolean-operator.rb",
+ "+++ b/boolean-operator.rb",
+ "@@ -1,3 +1,2 @@",
+ "-a && b",
+ "-a || b",
+ " a || b",
+ "+a && b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "448ad869895b76ca995e45d21a6f3b326fe2fb62"
+ "shas": "000c0198a566086df4d95a1ffd575748b7721552..f363216d5459fb0eafeb0168cc3f4af6d11f8cd5"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-test",
@@ -159,9 +205,17 @@
"filePaths": [
"boolean-operator.rb"
],
- "sha1": "448ad869895b76ca995e45d21a6f3b326fe2fb62",
+ "patch": [
+ "diff --git a/boolean-operator.rb b/boolean-operator.rb",
+ "index 32a41c9..b0af58d 100644",
+ "--- a/boolean-operator.rb",
+ "+++ b/boolean-operator.rb",
+ "@@ -1,2 +1 @@",
+ "-a || b",
+ " a && b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "fa9984bbc1cfa09937bf72c2218ec2bd233626de"
+ "shas": "f363216d5459fb0eafeb0168cc3f4af6d11f8cd5..57a8c0847390f2f78910231321007d7b2c86cc7a"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-rest-test",
@@ -190,7 +244,14 @@
"filePaths": [
"boolean-operator.rb"
],
- "sha1": "fa9984bbc1cfa09937bf72c2218ec2bd233626de",
+ "patch": [
+ "diff --git a/boolean-operator.rb b/boolean-operator.rb",
+ "index b0af58d..e69de29 100644",
+ "--- a/boolean-operator.rb",
+ "+++ b/boolean-operator.rb",
+ "@@ -1 +0,0 @@",
+ "-a && b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "ef97729fc1ce67c8c748ea440decb29ce2e8fb6e"
+ "shas": "57a8c0847390f2f78910231321007d7b2c86cc7a..0c8195a0d30149b84b53bc2c98687d24a787f4dd"
}]
diff --git a/test/corpus/diff-summaries/ruby/case-statement.json b/test/corpus/diff-summaries/ruby/case-statement.json
deleted file mode 100644
index 9bbeccc25..000000000
--- a/test/corpus/diff-summaries/ruby/case-statement.json
+++ /dev/null
@@ -1,262 +0,0 @@
-[{
- "testCaseDescription": "ruby-case-statement-insert-test",
- "expectedResult": {
- "changes": {
- "case-statement.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 4
- ]
- }
- },
- "summary": "Added the 'foo' switch statement"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "case-statement.rb"
- ],
- "sha1": "9b332f981a2fa42849e4ddc48afca9424480312d",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "91f8cf75d9c34e5b1275898ae984a110f3b6381b"
-}
-,{
- "testCaseDescription": "ruby-case-statement-replacement-insert-test",
- "expectedResult": {
- "changes": {
- "case-statement.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 4
- ]
- }
- },
- "summary": "Added the 'foo' switch statement"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 1
- ],
- "end": [
- 7,
- 4
- ]
- }
- },
- "summary": "Added the 'foo' switch statement"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "case-statement.rb"
- ],
- "sha1": "91f8cf75d9c34e5b1275898ae984a110f3b6381b",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "d7029d7b9e07992515a23b2410f68aa645c7ac04"
-}
-,{
- "testCaseDescription": "ruby-case-statement-delete-insert-test",
- "expectedResult": {
- "changes": {
- "case-statement.rb": [
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 3,
- 5
- ]
- }
- },
- "summary": "Deleted the 'else' expression statements"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "case-statement.rb"
- ],
- "sha1": "d7029d7b9e07992515a23b2410f68aa645c7ac04",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "6b2a37829199cf77bcbd27c3b0051cc0ea42e419"
-}
-,{
- "testCaseDescription": "ruby-case-statement-replacement-test",
- "expectedResult": {
- "changes": {
- "case-statement.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 3,
- 5
- ]
- }
- },
- "summary": "Added the 'else' expression statements"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "case-statement.rb"
- ],
- "sha1": "6b2a37829199cf77bcbd27c3b0051cc0ea42e419",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "6e0d7c355b6c2c3d21ea2c6ba4603039e4a80f38"
-}
-,{
- "testCaseDescription": "ruby-case-statement-delete-replacement-test",
- "expectedResult": {
- "changes": {
- "case-statement.rb": [
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 4
- ]
- }
- },
- "summary": "Deleted the 'foo' switch statement"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 1
- ],
- "end": [
- 7,
- 4
- ]
- }
- },
- "summary": "Deleted the 'foo' switch statement"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 1
- ],
- "end": [
- 7,
- 4
- ]
- }
- },
- "summary": "Added the 'foo' switch statement"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "case-statement.rb"
- ],
- "sha1": "6e0d7c355b6c2c3d21ea2c6ba4603039e4a80f38",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "62110252f65a05ba2d9acf0d52d78e00afecef6c"
-}
-,{
- "testCaseDescription": "ruby-case-statement-delete-test",
- "expectedResult": {
- "changes": {
- "case-statement.rb": [
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 4
- ]
- }
- },
- "summary": "Deleted the 'foo' switch statement"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "case-statement.rb"
- ],
- "sha1": "62110252f65a05ba2d9acf0d52d78e00afecef6c",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "6abb2ef55c040d5c19e14573d227d3ad04f387c0"
-}
-,{
- "testCaseDescription": "ruby-case-statement-delete-rest-test",
- "expectedResult": {
- "changes": {
- "case-statement.rb": [
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 4
- ]
- }
- },
- "summary": "Deleted the 'foo' switch statement"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "case-statement.rb"
- ],
- "sha1": "6abb2ef55c040d5c19e14573d227d3ad04f387c0",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "637106220ab216a08eb28519ce44928d8e58e145"
-}]
diff --git a/test/corpus/diff-summaries/ruby/class.json b/test/corpus/diff-summaries/ruby/class.json
index b79a8e5f9..e62e83f4d 100644
--- a/test/corpus/diff-summaries/ruby/class.json
+++ b/test/corpus/diff-summaries/ruby/class.json
@@ -25,9 +25,18 @@
"filePaths": [
"class.rb"
],
- "sha1": "637106220ab216a08eb28519ce44928d8e58e145",
+ "patch": [
+ "diff --git a/class.rb b/class.rb",
+ "index e69de29..81b916c 100644",
+ "--- a/class.rb",
+ "+++ b/class.rb",
+ "@@ -0,0 +1,3 @@",
+ "+class Foo < Super",
+ "+ def test; end",
+ "+end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "ff07bf79b05eebef0764a429680b0eebccc58883"
+ "shas": "98200bee05decb871fcfdf6858ee954898880f72..b6210fce75b001a4f6dcebfd8977c41c74c55e40"
}
,{
"testCaseDescription": "ruby-class-replacement-insert-test",
@@ -71,9 +80,24 @@
"filePaths": [
"class.rb"
],
- "sha1": "ff07bf79b05eebef0764a429680b0eebccc58883",
+ "patch": [
+ "diff --git a/class.rb b/class.rb",
+ "index 81b916c..e67922c 100644",
+ "--- a/class.rb",
+ "+++ b/class.rb",
+ "@@ -1,3 +1,9 @@",
+ "+class Foo",
+ "+ def test; end",
+ "+end",
+ "+class Foo < Super",
+ "+ def test; end",
+ "+end",
+ " class Foo < Super",
+ " def test; end",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "4db7f22a3d7477c156b1acd70cc15f8f88dde400"
+ "shas": "b6210fce75b001a4f6dcebfd8977c41c74c55e40..4d8c5346eda3e267a62cbe1cd2da74ff24035f5b"
}
,{
"testCaseDescription": "ruby-class-delete-insert-test",
@@ -84,9 +108,20 @@
"filePaths": [
"class.rb"
],
- "sha1": "4db7f22a3d7477c156b1acd70cc15f8f88dde400",
+ "patch": [
+ "diff --git a/class.rb b/class.rb",
+ "index e67922c..c371fd8 100644",
+ "--- a/class.rb",
+ "+++ b/class.rb",
+ "@@ -1,4 +1,4 @@",
+ "-class Foo",
+ "+class Foo < Super",
+ " def test; end",
+ " end",
+ " class Foo < Super"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "318aba9031607b1d1d37df4f673bf5d49f9a73a1"
+ "shas": "4d8c5346eda3e267a62cbe1cd2da74ff24035f5b..895b7645a3ad8b26bfb59f814bf914213a1508f8"
}
,{
"testCaseDescription": "ruby-class-replacement-test",
@@ -97,9 +132,20 @@
"filePaths": [
"class.rb"
],
- "sha1": "318aba9031607b1d1d37df4f673bf5d49f9a73a1",
+ "patch": [
+ "diff --git a/class.rb b/class.rb",
+ "index c371fd8..e67922c 100644",
+ "--- a/class.rb",
+ "+++ b/class.rb",
+ "@@ -1,4 +1,4 @@",
+ "-class Foo < Super",
+ "+class Foo",
+ " def test; end",
+ " end",
+ " class Foo < Super"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "25664d8665479723ed30e0d5ce8e6712e16a72ea"
+ "shas": "895b7645a3ad8b26bfb59f814bf914213a1508f8..64fd047eef7b0ce2ea5e8746e8d79b3ca8c0ec06"
}
,{
"testCaseDescription": "ruby-class-delete-replacement-test",
@@ -158,9 +204,25 @@
"filePaths": [
"class.rb"
],
- "sha1": "25664d8665479723ed30e0d5ce8e6712e16a72ea",
+ "patch": [
+ "diff --git a/class.rb b/class.rb",
+ "index e67922c..818d26a 100644",
+ "--- a/class.rb",
+ "+++ b/class.rb",
+ "@@ -1,9 +1,6 @@",
+ "-class Foo",
+ "- def test; end",
+ "-end",
+ " class Foo < Super",
+ " def test; end",
+ " end",
+ "-class Foo < Super",
+ "+class Foo",
+ " def test; end",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "25184ebb3d6c360f3fa65f679cc374bee476c62a"
+ "shas": "64fd047eef7b0ce2ea5e8746e8d79b3ca8c0ec06..129ea7453ad876f91980fe45c08f65586d0b082b"
}
,{
"testCaseDescription": "ruby-class-delete-test",
@@ -189,9 +251,21 @@
"filePaths": [
"class.rb"
],
- "sha1": "25184ebb3d6c360f3fa65f679cc374bee476c62a",
+ "patch": [
+ "diff --git a/class.rb b/class.rb",
+ "index 818d26a..bab2e9f 100644",
+ "--- a/class.rb",
+ "+++ b/class.rb",
+ "@@ -1,6 +1,3 @@",
+ "-class Foo < Super",
+ "- def test; end",
+ "-end",
+ " class Foo",
+ " def test; end",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "2031c76ba3543d413bee50ae682ff914a6e697ad"
+ "shas": "129ea7453ad876f91980fe45c08f65586d0b082b..7a054e58466e2a33d7c70bb948497f3b0622b6e5"
}
,{
"testCaseDescription": "ruby-class-delete-rest-test",
@@ -220,7 +294,16 @@
"filePaths": [
"class.rb"
],
- "sha1": "2031c76ba3543d413bee50ae682ff914a6e697ad",
+ "patch": [
+ "diff --git a/class.rb b/class.rb",
+ "index bab2e9f..e69de29 100644",
+ "--- a/class.rb",
+ "+++ b/class.rb",
+ "@@ -1,3 +0,0 @@",
+ "-class Foo",
+ "- def test; end",
+ "-end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "1b98fc53dd62922900312603c00866cd0981b695"
+ "shas": "7a054e58466e2a33d7c70bb948497f3b0622b6e5..5e4ebb1f424a9e273ffc7cc40c76cee1d78b0d77"
}]
diff --git a/test/corpus/diff-summaries/ruby/comment.json b/test/corpus/diff-summaries/ruby/comment.json
index 2835b1c9a..00c9e9eb8 100644
--- a/test/corpus/diff-summaries/ruby/comment.json
+++ b/test/corpus/diff-summaries/ruby/comment.json
@@ -7,9 +7,16 @@
"filePaths": [
"comment.rb"
],
- "sha1": "9e7143591420559db8bb6c8648077d460d371b9f",
+ "patch": [
+ "diff --git a/comment.rb b/comment.rb",
+ "index e69de29..7dd15c1 100644",
+ "--- a/comment.rb",
+ "+++ b/comment.rb",
+ "@@ -0,0 +1 @@",
+ "+# This is a comment"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "f046eeeed6eff9186064ab755e813bc89b8cc39c"
+ "shas": "a07f2fef830bc79ffa2136025c4e29d5c8a0ff1b..d3d916a02cf198fb7c5c5f96df6b1fc4382b76e8"
}
,{
"testCaseDescription": "ruby-comment-replacement-insert-test",
@@ -20,9 +27,21 @@
"filePaths": [
"comment.rb"
],
- "sha1": "f046eeeed6eff9186064ab755e813bc89b8cc39c",
+ "patch": [
+ "diff --git a/comment.rb b/comment.rb",
+ "index 7dd15c1..ef7e0e6 100644",
+ "--- a/comment.rb",
+ "+++ b/comment.rb",
+ "@@ -1 +1,6 @@",
+ "+=begin",
+ "+This is a multiline",
+ "+comment",
+ "+=end",
+ "+# This is a comment",
+ " # This is a comment"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e15daa6b2b08a29755c53ce3c4429f249f6987e3"
+ "shas": "d3d916a02cf198fb7c5c5f96df6b1fc4382b76e8..f7b133e4dd896586ba44964a6d2bd39a6127add3"
}
,{
"testCaseDescription": "ruby-comment-delete-insert-test",
@@ -33,9 +52,22 @@
"filePaths": [
"comment.rb"
],
- "sha1": "e15daa6b2b08a29755c53ce3c4429f249f6987e3",
+ "patch": [
+ "diff --git a/comment.rb b/comment.rb",
+ "index ef7e0e6..b2a9858 100644",
+ "--- a/comment.rb",
+ "+++ b/comment.rb",
+ "@@ -1,6 +1,3 @@",
+ "-=begin",
+ "-This is a multiline",
+ "-comment",
+ "-=end",
+ "+# This is a comment",
+ " # This is a comment",
+ " # This is a comment"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "75a598a45ac4a97d739989a173431c38ebc6ed9f"
+ "shas": "f7b133e4dd896586ba44964a6d2bd39a6127add3..0a2c056dcc8f63a3911048c316c580cf4252efc7"
}
,{
"testCaseDescription": "ruby-comment-replacement-test",
@@ -46,9 +78,22 @@
"filePaths": [
"comment.rb"
],
- "sha1": "75a598a45ac4a97d739989a173431c38ebc6ed9f",
+ "patch": [
+ "diff --git a/comment.rb b/comment.rb",
+ "index b2a9858..ef7e0e6 100644",
+ "--- a/comment.rb",
+ "+++ b/comment.rb",
+ "@@ -1,3 +1,6 @@",
+ "-# This is a comment",
+ "+=begin",
+ "+This is a multiline",
+ "+comment",
+ "+=end",
+ " # This is a comment",
+ " # This is a comment"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "7bf58b87b23ef2acbed429beb982a3acf53e83f3"
+ "shas": "0a2c056dcc8f63a3911048c316c580cf4252efc7..bf6bbf3aa85c998bbea81e8fcd8c51057e9a843c"
}
,{
"testCaseDescription": "ruby-comment-delete-replacement-test",
@@ -59,9 +104,22 @@
"filePaths": [
"comment.rb"
],
- "sha1": "7bf58b87b23ef2acbed429beb982a3acf53e83f3",
+ "patch": [
+ "diff --git a/comment.rb b/comment.rb",
+ "index ef7e0e6..787b019 100644",
+ "--- a/comment.rb",
+ "+++ b/comment.rb",
+ "@@ -1,6 +1,5 @@",
+ "+# This is a comment",
+ " =begin",
+ " This is a multiline",
+ " comment",
+ " =end",
+ "-# This is a comment",
+ "-# This is a comment"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e46bfe9cc1b0cb70c5fdab5ffb299add7479d6da"
+ "shas": "bf6bbf3aa85c998bbea81e8fcd8c51057e9a843c..c7b39074cc7505098417f848da30325ca8b7410f"
}
,{
"testCaseDescription": "ruby-comment-delete-test",
@@ -72,9 +130,19 @@
"filePaths": [
"comment.rb"
],
- "sha1": "e46bfe9cc1b0cb70c5fdab5ffb299add7479d6da",
+ "patch": [
+ "diff --git a/comment.rb b/comment.rb",
+ "index 787b019..5bbcda3 100644",
+ "--- a/comment.rb",
+ "+++ b/comment.rb",
+ "@@ -1,4 +1,3 @@",
+ "-# This is a comment",
+ " =begin",
+ " This is a multiline",
+ " comment"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "5983ba2631f2b1fc3b60b7147eb6f315fcfeb7de"
+ "shas": "c7b39074cc7505098417f848da30325ca8b7410f..ef695b264a83cfc43b8b08eb4bfcd4f22fa138d1"
}
,{
"testCaseDescription": "ruby-comment-delete-rest-test",
@@ -85,7 +153,17 @@
"filePaths": [
"comment.rb"
],
- "sha1": "5983ba2631f2b1fc3b60b7147eb6f315fcfeb7de",
+ "patch": [
+ "diff --git a/comment.rb b/comment.rb",
+ "index 5bbcda3..e69de29 100644",
+ "--- a/comment.rb",
+ "+++ b/comment.rb",
+ "@@ -1,4 +0,0 @@",
+ "-=begin",
+ "-This is a multiline",
+ "-comment",
+ "-=end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "0957bae761de5bf738359a6690f06c633b38a43d"
+ "shas": "ef695b264a83cfc43b8b08eb4bfcd4f22fa138d1..0f08e943de503b5d714186206425966f0517ddec"
}]
diff --git a/test/corpus/diff-summaries/ruby/comparision-operator.json b/test/corpus/diff-summaries/ruby/comparision-operator.json
index c40579fb3..1c6c8b5a8 100644
--- a/test/corpus/diff-summaries/ruby/comparision-operator.json
+++ b/test/corpus/diff-summaries/ruby/comparision-operator.json
@@ -40,9 +40,17 @@
"filePaths": [
"comparision-operator.rb"
],
- "sha1": "b5ca633b949a2227913a944093e291dd78724130",
+ "patch": [
+ "diff --git a/comparision-operator.rb b/comparision-operator.rb",
+ "index e69de29..582cb83 100644",
+ "--- a/comparision-operator.rb",
+ "+++ b/comparision-operator.rb",
+ "@@ -0,0 +1,2 @@",
+ "+x < y",
+ "+a > b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "5c0df13b4e946060b5bb8a3f567e6266765d89ae"
+ "shas": "cc9a4a6fa2a1c65983250a900daf6501538b4cd8..d0eb4857f83d5eef8c789d9b1800947161d8876d"
}
,{
"testCaseDescription": "ruby-comparision-operator-replacement-insert-test",
@@ -116,9 +124,21 @@
"filePaths": [
"comparision-operator.rb"
],
- "sha1": "5c0df13b4e946060b5bb8a3f567e6266765d89ae",
+ "patch": [
+ "diff --git a/comparision-operator.rb b/comparision-operator.rb",
+ "index 582cb83..b96996d 100644",
+ "--- a/comparision-operator.rb",
+ "+++ b/comparision-operator.rb",
+ "@@ -1,2 +1,6 @@",
+ "+x <= y",
+ "+a >= b",
+ "+x < y",
+ "+a > b",
+ " x < y",
+ " a > b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "98b281bba1a406ad126b10a93b1f19a6ec904e3d"
+ "shas": "d0eb4857f83d5eef8c789d9b1800947161d8876d..186f6c1cb9c2260246f3126b1203b54b9670ea09"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-insert-test",
@@ -129,9 +149,22 @@
"filePaths": [
"comparision-operator.rb"
],
- "sha1": "98b281bba1a406ad126b10a93b1f19a6ec904e3d",
+ "patch": [
+ "diff --git a/comparision-operator.rb b/comparision-operator.rb",
+ "index b96996d..3b7fde7 100644",
+ "--- a/comparision-operator.rb",
+ "+++ b/comparision-operator.rb",
+ "@@ -1,5 +1,5 @@",
+ "-x <= y",
+ "-a >= b",
+ "+x < y",
+ "+a > b",
+ " x < y",
+ " a > b",
+ " x < y"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "609ac7fdd65830075d5e5020d98a1d0034003e13"
+ "shas": "186f6c1cb9c2260246f3126b1203b54b9670ea09..4e7370cd85c7f324871137855a459a1c583bce75"
}
,{
"testCaseDescription": "ruby-comparision-operator-replacement-test",
@@ -142,9 +175,22 @@
"filePaths": [
"comparision-operator.rb"
],
- "sha1": "609ac7fdd65830075d5e5020d98a1d0034003e13",
+ "patch": [
+ "diff --git a/comparision-operator.rb b/comparision-operator.rb",
+ "index 3b7fde7..b96996d 100644",
+ "--- a/comparision-operator.rb",
+ "+++ b/comparision-operator.rb",
+ "@@ -1,5 +1,5 @@",
+ "-x < y",
+ "-a > b",
+ "+x <= y",
+ "+a >= b",
+ " x < y",
+ " a > b",
+ " x < y"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "4e8293b3761bd1e979438bcbfd0315930b5392a7"
+ "shas": "4e7370cd85c7f324871137855a459a1c583bce75..a26bfabeda46c054da38b6aaf5564c5b9e575294"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-replacement-test",
@@ -188,9 +234,23 @@
"filePaths": [
"comparision-operator.rb"
],
- "sha1": "4e8293b3761bd1e979438bcbfd0315930b5392a7",
+ "patch": [
+ "diff --git a/comparision-operator.rb b/comparision-operator.rb",
+ "index b96996d..1cfa010 100644",
+ "--- a/comparision-operator.rb",
+ "+++ b/comparision-operator.rb",
+ "@@ -1,6 +1,4 @@",
+ "-x <= y",
+ "-a >= b",
+ "-x < y",
+ "-a > b",
+ " x < y",
+ " a > b",
+ "+x <= y",
+ "+a >= b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "d5eeac3751d6ec5815784b8f52c55a394b27e8a3"
+ "shas": "a26bfabeda46c054da38b6aaf5564c5b9e575294..0e4db6b78d0c970ab1b1c30a357997ccd2dd80fa"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-test",
@@ -234,9 +294,19 @@
"filePaths": [
"comparision-operator.rb"
],
- "sha1": "d5eeac3751d6ec5815784b8f52c55a394b27e8a3",
+ "patch": [
+ "diff --git a/comparision-operator.rb b/comparision-operator.rb",
+ "index 1cfa010..71b2892 100644",
+ "--- a/comparision-operator.rb",
+ "+++ b/comparision-operator.rb",
+ "@@ -1,4 +1,2 @@",
+ "-x < y",
+ "-a > b",
+ " x <= y",
+ " a >= b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "035c31d7e8d2ea156414abf017c7ddca7296334c"
+ "shas": "0e4db6b78d0c970ab1b1c30a357997ccd2dd80fa..84a86501aebef11b8627b8524fc8d324665ffc44"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-rest-test",
@@ -280,7 +350,15 @@
"filePaths": [
"comparision-operator.rb"
],
- "sha1": "035c31d7e8d2ea156414abf017c7ddca7296334c",
+ "patch": [
+ "diff --git a/comparision-operator.rb b/comparision-operator.rb",
+ "index 71b2892..e69de29 100644",
+ "--- a/comparision-operator.rb",
+ "+++ b/comparision-operator.rb",
+ "@@ -1,2 +0,0 @@",
+ "-x <= y",
+ "-a >= b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "85eb09d96abcd8b75415cc71358b6753031dd375"
+ "shas": "84a86501aebef11b8627b8524fc8d324665ffc44..70d36a6a9817b1e91707c1f7f830a0568b959efa"
}]
diff --git a/test/corpus/diff-summaries/ruby/conditional-assignment.json b/test/corpus/diff-summaries/ruby/conditional-assignment.json
index 5ae03ff4f..25744554c 100644
--- a/test/corpus/diff-summaries/ruby/conditional-assignment.json
+++ b/test/corpus/diff-summaries/ruby/conditional-assignment.json
@@ -25,9 +25,16 @@
"filePaths": [
"conditional-assignment.rb"
],
- "sha1": "d969215f4dc1f8fcdb7936be60bd0ac51877cea9",
+ "patch": [
+ "diff --git a/conditional-assignment.rb b/conditional-assignment.rb",
+ "index e69de29..f8f538b 100644",
+ "--- a/conditional-assignment.rb",
+ "+++ b/conditional-assignment.rb",
+ "@@ -0,0 +1 @@",
+ "+x ||= 5"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e7df092e38108876d5bbd8167ff092d1e5bcef0c"
+ "shas": "6564c9c8832540d910a4118a6130305613ef9772..737bffe1cb105e55eb30dcb5e66499a162216c4d"
}
,{
"testCaseDescription": "ruby-conditional-assignment-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"conditional-assignment.rb"
],
- "sha1": "e7df092e38108876d5bbd8167ff092d1e5bcef0c",
+ "patch": [
+ "diff --git a/conditional-assignment.rb b/conditional-assignment.rb",
+ "index f8f538b..6c10ae5 100644",
+ "--- a/conditional-assignment.rb",
+ "+++ b/conditional-assignment.rb",
+ "@@ -1 +1,3 @@",
+ "+x &&= 7",
+ "+x ||= 5",
+ " x ||= 5"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "a3c46cd5e4d07efa83e2bba95552b06a2e270550"
+ "shas": "737bffe1cb105e55eb30dcb5e66499a162216c4d..b4680d4032610561ef31cbb0508bfc9573be0d0c"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"conditional-assignment.rb"
],
- "sha1": "a3c46cd5e4d07efa83e2bba95552b06a2e270550",
+ "patch": [
+ "diff --git a/conditional-assignment.rb b/conditional-assignment.rb",
+ "index 6c10ae5..a333810 100644",
+ "--- a/conditional-assignment.rb",
+ "+++ b/conditional-assignment.rb",
+ "@@ -1,3 +1,3 @@",
+ "-x &&= 7",
+ "+x ||= 5",
+ " x ||= 5",
+ " x ||= 5"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "d69c2aeeb2f5662a480fc0a5863c0e37957defe5"
+ "shas": "b4680d4032610561ef31cbb0508bfc9573be0d0c..cce1693dd4e7b6101f7cbcc9100b4c3276194fa2"
}
,{
"testCaseDescription": "ruby-conditional-assignment-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"conditional-assignment.rb"
],
- "sha1": "d69c2aeeb2f5662a480fc0a5863c0e37957defe5",
+ "patch": [
+ "diff --git a/conditional-assignment.rb b/conditional-assignment.rb",
+ "index a333810..6c10ae5 100644",
+ "--- a/conditional-assignment.rb",
+ "+++ b/conditional-assignment.rb",
+ "@@ -1,3 +1,3 @@",
+ "-x ||= 5",
+ "+x &&= 7",
+ " x ||= 5",
+ " x ||= 5"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "d3af4b3df061945f9a28f9b5994dbdbba51f1531"
+ "shas": "cce1693dd4e7b6101f7cbcc9100b4c3276194fa2..8bd810b4f976b9701ff7a0ceb9d018bfeac4780e"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"conditional-assignment.rb"
],
- "sha1": "d3af4b3df061945f9a28f9b5994dbdbba51f1531",
+ "patch": [
+ "diff --git a/conditional-assignment.rb b/conditional-assignment.rb",
+ "index 6c10ae5..a56ffee 100644",
+ "--- a/conditional-assignment.rb",
+ "+++ b/conditional-assignment.rb",
+ "@@ -1,3 +1,2 @@",
+ "-x &&= 7",
+ "-x ||= 5",
+ " x ||= 5",
+ "+x &&= 7"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "3a293566ed56e21f15702c3ac7daa8eed77f2e4c"
+ "shas": "8bd810b4f976b9701ff7a0ceb9d018bfeac4780e..ddc2e0154b1f8cbb3c3e3800549d0c5126c7ff52"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"conditional-assignment.rb"
],
- "sha1": "3a293566ed56e21f15702c3ac7daa8eed77f2e4c",
+ "patch": [
+ "diff --git a/conditional-assignment.rb b/conditional-assignment.rb",
+ "index a56ffee..1abca02 100644",
+ "--- a/conditional-assignment.rb",
+ "+++ b/conditional-assignment.rb",
+ "@@ -1,2 +1 @@",
+ "-x ||= 5",
+ " x &&= 7"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "2f43f8e7b848807903813396b3be87f10f632f57"
+ "shas": "ddc2e0154b1f8cbb3c3e3800549d0c5126c7ff52..4f41d6075e03521d205fb38e22fe31e8f89ffcd9"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"conditional-assignment.rb"
],
- "sha1": "2f43f8e7b848807903813396b3be87f10f632f57",
+ "patch": [
+ "diff --git a/conditional-assignment.rb b/conditional-assignment.rb",
+ "index 1abca02..e69de29 100644",
+ "--- a/conditional-assignment.rb",
+ "+++ b/conditional-assignment.rb",
+ "@@ -1 +0,0 @@",
+ "-x &&= 7"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "65cdd278c64ea23aacd3c8cf11e6f52864fa66ff"
+ "shas": "4f41d6075e03521d205fb38e22fe31e8f89ffcd9..78a9116b77a62e27008d72a5a1f2b1b9bec795bd"
}]
diff --git a/test/corpus/diff-summaries/ruby/delimiter.json b/test/corpus/diff-summaries/ruby/delimiter.json
index ca0a760f0..4287293ac 100644
--- a/test/corpus/diff-summaries/ruby/delimiter.json
+++ b/test/corpus/diff-summaries/ruby/delimiter.json
@@ -100,9 +100,21 @@
"filePaths": [
"delimiter.rb"
],
- "sha1": "0de5663fae24bc6af3327776d01518ef6a240ed6",
+ "patch": [
+ "diff --git a/delimiter.rb b/delimiter.rb",
+ "index e69de29..8ec39b8 100644",
+ "--- a/delimiter.rb",
+ "+++ b/delimiter.rb",
+ "@@ -0,0 +1,6 @@",
+ "+%q#a#",
+ "+%qc>",
+ "+%#a#",
+ "+%Q#a#",
+ "+%c>",
+ "+%Qc>"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "f0bcca3b78103200fb1d40626eacace4e8b877ec"
+ "shas": "ef8d34476c23317120bf744df9d41b9110a04c03..1b0f7afd8b56c527a93bcf77cd130a197736aae8"
}
,{
"testCaseDescription": "ruby-delimiter-replacement-insert-test",
@@ -296,9 +308,30 @@
"filePaths": [
"delimiter.rb"
],
- "sha1": "f0bcca3b78103200fb1d40626eacace4e8b877ec",
+ "patch": [
+ "diff --git a/delimiter.rb b/delimiter.rb",
+ "index 8ec39b8..5b0f7ec 100644",
+ "--- a/delimiter.rb",
+ "+++ b/delimiter.rb",
+ "@@ -1,3 +1,15 @@",
+ "+%q/b/",
+ "+%q{d{e}f}",
+ "+%/b/",
+ "+%Q/b/",
+ "+%{d{e}f}",
+ "+%Q{d{e}f}",
+ "+%q#a#",
+ "+%qc>",
+ "+%#a#",
+ "+%Q#a#",
+ "+%c>",
+ "+%Qc>",
+ " %q#a#",
+ " %qc>",
+ " %#a#"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "b0992b622b59aa994f8d0548e9dd527f13c0e03f"
+ "shas": "1b0f7afd8b56c527a93bcf77cd130a197736aae8..4e8d0a2cbe3dfca073f23bbb72b1461e5963338e"
}
,{
"testCaseDescription": "ruby-delimiter-delete-insert-test",
@@ -489,9 +522,30 @@
"filePaths": [
"delimiter.rb"
],
- "sha1": "b0992b622b59aa994f8d0548e9dd527f13c0e03f",
+ "patch": [
+ "diff --git a/delimiter.rb b/delimiter.rb",
+ "index 5b0f7ec..64d6df4 100644",
+ "--- a/delimiter.rb",
+ "+++ b/delimiter.rb",
+ "@@ -1,9 +1,9 @@",
+ "-%q/b/",
+ "-%q{d{e}f}",
+ "-%/b/",
+ "-%Q/b/",
+ "-%{d{e}f}",
+ "-%Q{d{e}f}",
+ "+%q#a#",
+ "+%qc>",
+ "+%#a#",
+ "+%Q#a#",
+ "+%c>",
+ "+%Qc>",
+ " %q#a#",
+ " %qc>",
+ " %#a#"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "4b10babb959cbc872eba8ed8cd0691dbed4d419b"
+ "shas": "4e8d0a2cbe3dfca073f23bbb72b1461e5963338e..413fa9f465cd1591ad3c753e6d5d160ac0503019"
}
,{
"testCaseDescription": "ruby-delimiter-replacement-test",
@@ -676,9 +730,30 @@
"filePaths": [
"delimiter.rb"
],
- "sha1": "4b10babb959cbc872eba8ed8cd0691dbed4d419b",
+ "patch": [
+ "diff --git a/delimiter.rb b/delimiter.rb",
+ "index 64d6df4..5b0f7ec 100644",
+ "--- a/delimiter.rb",
+ "+++ b/delimiter.rb",
+ "@@ -1,9 +1,9 @@",
+ "-%q#a#",
+ "-%qc>",
+ "-%#a#",
+ "-%Q#a#",
+ "-%c>",
+ "-%Qc>",
+ "+%q/b/",
+ "+%q{d{e}f}",
+ "+%/b/",
+ "+%Q/b/",
+ "+%{d{e}f}",
+ "+%Q{d{e}f}",
+ " %q#a#",
+ " %qc>",
+ " %#a#"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "c410440c4904ca7b9e06a9e4db52140b5c4f3efa"
+ "shas": "413fa9f465cd1591ad3c753e6d5d160ac0503019..2a8902902ea697fda4a67838615f8b6a8e108353"
}
,{
"testCaseDescription": "ruby-delimiter-delete-replacement-test",
@@ -962,9 +1037,39 @@
"filePaths": [
"delimiter.rb"
],
- "sha1": "c410440c4904ca7b9e06a9e4db52140b5c4f3efa",
+ "patch": [
+ "diff --git a/delimiter.rb b/delimiter.rb",
+ "index 5b0f7ec..2095136 100644",
+ "--- a/delimiter.rb",
+ "+++ b/delimiter.rb",
+ "@@ -1,18 +1,12 @@",
+ "-%q/b/",
+ "-%q{d{e}f}",
+ "-%/b/",
+ "-%Q/b/",
+ "-%{d{e}f}",
+ "-%Q{d{e}f}",
+ "-%q#a#",
+ "-%qc>",
+ "-%#a#",
+ "-%Q#a#",
+ "-%c>",
+ "-%Qc>",
+ " %q#a#",
+ " %qc>",
+ " %#a#",
+ " %Q#a#",
+ " %c>",
+ " %Qc>",
+ "+%q/b/",
+ "+%q{d{e}f}",
+ "+%/b/",
+ "+%Q/b/",
+ "+%{d{e}f}",
+ "+%Q{d{e}f}"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "5d0108e6748974cdac94c56a1fba8c9a85776e4a"
+ "shas": "2a8902902ea697fda4a67838615f8b6a8e108353..c03569b5f580bc90dc6d65cdd1ec2c719444ce89"
}
,{
"testCaseDescription": "ruby-delimiter-delete-test",
@@ -1068,9 +1173,24 @@
"filePaths": [
"delimiter.rb"
],
- "sha1": "5d0108e6748974cdac94c56a1fba8c9a85776e4a",
+ "patch": [
+ "diff --git a/delimiter.rb b/delimiter.rb",
+ "index 2095136..3843090 100644",
+ "--- a/delimiter.rb",
+ "+++ b/delimiter.rb",
+ "@@ -1,9 +1,3 @@",
+ "-%q#a#",
+ "-%qc>",
+ "-%#a#",
+ "-%Q#a#",
+ "-%c>",
+ "-%Qc>",
+ " %q/b/",
+ " %q{d{e}f}",
+ " %/b/"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "2951208459503219639748c4432005ad8fb2cec7"
+ "shas": "c03569b5f580bc90dc6d65cdd1ec2c719444ce89..e9178c14220997160dfe6c89506972e0b7e1f258"
}
,{
"testCaseDescription": "ruby-delimiter-delete-rest-test",
@@ -1174,7 +1294,19 @@
"filePaths": [
"delimiter.rb"
],
- "sha1": "2951208459503219639748c4432005ad8fb2cec7",
+ "patch": [
+ "diff --git a/delimiter.rb b/delimiter.rb",
+ "index 3843090..e69de29 100644",
+ "--- a/delimiter.rb",
+ "+++ b/delimiter.rb",
+ "@@ -1,6 +0,0 @@",
+ "-%q/b/",
+ "-%q{d{e}f}",
+ "-%/b/",
+ "-%Q/b/",
+ "-%{d{e}f}",
+ "-%Q{d{e}f}"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "744a2cfc2e71f66e365ea3929763711025960196"
+ "shas": "e9178c14220997160dfe6c89506972e0b7e1f258..b8a1e5f549bc1fa5a1424093d499d32fa0987cee"
}]
diff --git a/test/corpus/diff-summaries/ruby/element-reference.json b/test/corpus/diff-summaries/ruby/element-reference.json
index 63caf5b66..081f3f9a7 100644
--- a/test/corpus/diff-summaries/ruby/element-reference.json
+++ b/test/corpus/diff-summaries/ruby/element-reference.json
@@ -55,9 +55,18 @@
"filePaths": [
"element-reference.rb"
],
- "sha1": "6bef099d2af7b41f171358e66662163cdf0bc96e",
+ "patch": [
+ "diff --git a/element-reference.rb b/element-reference.rb",
+ "index e69de29..f088562 100644",
+ "--- a/element-reference.rb",
+ "+++ b/element-reference.rb",
+ "@@ -0,0 +1,3 @@",
+ "+foo[bar]",
+ "+foo[:bar]",
+ "+foo[bar] = 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "8bc26414118839cc62822f791546a858daf7463d"
+ "shas": "72f935172c31da7ddd21bf1a12c7baeb4fdb3419..1b88f5fd6eaa6af48eef0522c818919cc89fe0f3"
}
,{
"testCaseDescription": "ruby-element-reference-replacement-insert-test",
@@ -146,9 +155,23 @@
"filePaths": [
"element-reference.rb"
],
- "sha1": "8bc26414118839cc62822f791546a858daf7463d",
+ "patch": [
+ "diff --git a/element-reference.rb b/element-reference.rb",
+ "index f088562..7c45cae 100644",
+ "--- a/element-reference.rb",
+ "+++ b/element-reference.rb",
+ "@@ -1,3 +1,8 @@",
+ "+x[\"b\"]",
+ "+x[:\"c\"]",
+ "+foo[bar]",
+ "+foo[:bar]",
+ "+foo[bar] = 1",
+ " foo[bar]",
+ " foo[:bar]",
+ " foo[bar] = 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "5bf31b94df885fc6aeef3d941a276275a1b54539"
+ "shas": "1b88f5fd6eaa6af48eef0522c818919cc89fe0f3..3114590b91f23ee9d8e9656e3c597b7710c5f08a"
}
,{
"testCaseDescription": "ruby-element-reference-delete-insert-test",
@@ -258,9 +281,23 @@
"filePaths": [
"element-reference.rb"
],
- "sha1": "5bf31b94df885fc6aeef3d941a276275a1b54539",
+ "patch": [
+ "diff --git a/element-reference.rb b/element-reference.rb",
+ "index 7c45cae..8e3c23d 100644",
+ "--- a/element-reference.rb",
+ "+++ b/element-reference.rb",
+ "@@ -1,5 +1,6 @@",
+ "-x[\"b\"]",
+ "-x[:\"c\"]",
+ "+foo[bar]",
+ "+foo[:bar]",
+ "+foo[bar] = 1",
+ " foo[bar]",
+ " foo[:bar]",
+ " foo[bar] = 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "2772d28a1314eea9589d8248bfaacaac641d78fd"
+ "shas": "3114590b91f23ee9d8e9656e3c597b7710c5f08a..470abdcd5adc26a44bbd001539d731e36d417046"
}
,{
"testCaseDescription": "ruby-element-reference-replacement-test",
@@ -370,9 +407,23 @@
"filePaths": [
"element-reference.rb"
],
- "sha1": "2772d28a1314eea9589d8248bfaacaac641d78fd",
+ "patch": [
+ "diff --git a/element-reference.rb b/element-reference.rb",
+ "index 8e3c23d..7c45cae 100644",
+ "--- a/element-reference.rb",
+ "+++ b/element-reference.rb",
+ "@@ -1,6 +1,5 @@",
+ "-foo[bar]",
+ "-foo[:bar]",
+ "-foo[bar] = 1",
+ "+x[\"b\"]",
+ "+x[:\"c\"]",
+ " foo[bar]",
+ " foo[:bar]",
+ " foo[bar] = 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "6bd4d2e07d73b6bf4d52cff5ec3990c18e04da38"
+ "shas": "470abdcd5adc26a44bbd001539d731e36d417046..ee5fbeec520aa431dcf290c4a7eb220d2bb2b674"
}
,{
"testCaseDescription": "ruby-element-reference-delete-replacement-test",
@@ -491,9 +542,25 @@
"filePaths": [
"element-reference.rb"
],
- "sha1": "6bd4d2e07d73b6bf4d52cff5ec3990c18e04da38",
+ "patch": [
+ "diff --git a/element-reference.rb b/element-reference.rb",
+ "index 7c45cae..165629c 100644",
+ "--- a/element-reference.rb",
+ "+++ b/element-reference.rb",
+ "@@ -1,8 +1,5 @@",
+ "-x[\"b\"]",
+ "-x[:\"c\"]",
+ "-foo[bar]",
+ "-foo[:bar]",
+ "-foo[bar] = 1",
+ " foo[bar]",
+ " foo[:bar]",
+ " foo[bar] = 1",
+ "+x[\"b\"]",
+ "+x[:\"c\"]"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "69629c98667b474becb7b596dedd4133cd703449"
+ "shas": "ee5fbeec520aa431dcf290c4a7eb220d2bb2b674..3fb44d52e9f12fd560773298d89b1721698f358a"
}
,{
"testCaseDescription": "ruby-element-reference-delete-test",
@@ -552,9 +619,20 @@
"filePaths": [
"element-reference.rb"
],
- "sha1": "69629c98667b474becb7b596dedd4133cd703449",
+ "patch": [
+ "diff --git a/element-reference.rb b/element-reference.rb",
+ "index 165629c..d1fa515 100644",
+ "--- a/element-reference.rb",
+ "+++ b/element-reference.rb",
+ "@@ -1,5 +1,2 @@",
+ "-foo[bar]",
+ "-foo[:bar]",
+ "-foo[bar] = 1",
+ " x[\"b\"]",
+ " x[:\"c\"]"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "65dc4b08527a43bdf462865885355973c8154460"
+ "shas": "3fb44d52e9f12fd560773298d89b1721698f358a..0207d27c72e4662c924f3f408396247dbc990739"
}
,{
"testCaseDescription": "ruby-element-reference-delete-rest-test",
@@ -598,7 +676,15 @@
"filePaths": [
"element-reference.rb"
],
- "sha1": "65dc4b08527a43bdf462865885355973c8154460",
+ "patch": [
+ "diff --git a/element-reference.rb b/element-reference.rb",
+ "index d1fa515..e69de29 100644",
+ "--- a/element-reference.rb",
+ "+++ b/element-reference.rb",
+ "@@ -1,2 +0,0 @@",
+ "-x[\"b\"]",
+ "-x[:\"c\"]"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "0afd2cfcf489061cc131d9970716bb04bb5cb203"
+ "shas": "0207d27c72e4662c924f3f408396247dbc990739..72e1f4912f54a936266422abbb53a9c2fc864992"
}]
diff --git a/test/corpus/diff-summaries/ruby/else.json b/test/corpus/diff-summaries/ruby/else.json
new file mode 100644
index 000000000..50b53b56c
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/else.json
@@ -0,0 +1,270 @@
+[{
+ "testCaseDescription": "ruby-else-setup-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index e69de29..d2757f9 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -0,0 +1,3 @@",
+ "+begin",
+ "+ foo()",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "4fed48f0abf8058f93dbb4c7361358c434c9bb6d..e1fa35de3fc02773c68ea68b126d5a42843cff03"
+}
+,{
+ "testCaseDescription": "ruby-else-insert-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Added an else block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index d2757f9..09f6b12 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -1,3 +1,4 @@",
+ " begin",
+ " foo()",
+ "+else",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "e1fa35de3fc02773c68ea68b126d5a42843cff03..37109135d5e8872de06650f214f53d5782718911"
+}
+,{
+ "testCaseDescription": "ruby-else-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ },
+ {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced an else block with an 'bar()' function call in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index 09f6b12..f9c269d 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -1,4 +1,5 @@",
+ " begin",
+ " foo()",
+ " else",
+ "+ bar()",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "37109135d5e8872de06650f214f53d5782718911..e9f5d111cea4eb38ef60719ace819f23d38d2c7b"
+}
+,{
+ "testCaseDescription": "ruby-else-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ },
+ {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'bar()' function call with the else block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index f9c269d..09f6b12 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -1,5 +1,4 @@",
+ " begin",
+ " foo()",
+ " else",
+ "- bar()",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "e9f5d111cea4eb38ef60719ace819f23d38d2c7b..343ff65611626b914e8d8a3e97c6159ef40e1262"
+}
+,{
+ "testCaseDescription": "ruby-else-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted an else block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index 09f6b12..d2757f9 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -1,4 +1,3 @@",
+ " begin",
+ " foo()",
+ "-else",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "343ff65611626b914e8d8a3e97c6159ef40e1262..d849d51a7355131232dbf59bd5b3d20fa660b059"
+}
+,{
+ "testCaseDescription": "ruby-else-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index d2757f9..e69de29 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -1,3 +0,0 @@",
+ "-begin",
+ "- foo()",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d849d51a7355131232dbf59bd5b3d20fa660b059..f6f1229dfdaa0bf7f5b33425764b3b4423e6e28c"
+}]
diff --git a/test/corpus/diff-summaries/ruby/elsif.json b/test/corpus/diff-summaries/ruby/elsif.json
new file mode 100644
index 000000000..42cf7a6f2
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/elsif.json
@@ -0,0 +1,246 @@
+[{
+ "testCaseDescription": "ruby-elsif-setup-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'bar' if statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index e69de29..89b5cd5 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -0,0 +1,3 @@",
+ "+if bar",
+ "+ foo()",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d571b61c3d53f568ed84cc6dad1c76cea2abe08d..adfbf640ca01c2a8140a30b71499b03d8e9602db"
+}
+,{
+ "testCaseDescription": "ruby-elsif-insert-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 4,
+ 1
+ ]
+ }
+ },
+ "summary": "Added the 'baz' elsif block in the 'bar' if statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index 89b5cd5..945e953 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -1,3 +1,4 @@",
+ " if bar",
+ " foo()",
+ "+elsif baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "adfbf640ca01c2a8140a30b71499b03d8e9602db..c56c2c77e578103675c05343baa6ac9b57de69c9"
+}
+,{
+ "testCaseDescription": "ruby-elsif-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'qoz()' function call in the 'baz' elsif block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index 945e953..8e4733f 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -1,4 +1,5 @@",
+ " if bar",
+ " foo()",
+ " elsif baz",
+ "+ qoz()",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c56c2c77e578103675c05343baa6ac9b57de69c9..9d868b4d65a258ca50a0432f32d6ce476a0ec90b"
+}
+,{
+ "testCaseDescription": "ruby-elsif-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'qoz()' function call in the 'baz' elsif block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index 8e4733f..945e953 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -1,5 +1,4 @@",
+ " if bar",
+ " foo()",
+ " elsif baz",
+ "- qoz()",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "9d868b4d65a258ca50a0432f32d6ce476a0ec90b..ae5492ab9e3097846c7c9365e1dba37799da7cf0"
+}
+,{
+ "testCaseDescription": "ruby-elsif-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 4,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the 'baz' elsif block in the 'bar' if statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index 945e953..89b5cd5 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -1,4 +1,3 @@",
+ " if bar",
+ " foo()",
+ "-elsif baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "ae5492ab9e3097846c7c9365e1dba37799da7cf0..3c79699074347065dc50d414845fc7dada45dc0e"
+}
+,{
+ "testCaseDescription": "ruby-elsif-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' if statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index 89b5cd5..e69de29 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -1,3 +0,0 @@",
+ "-if bar",
+ "- foo()",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "3c79699074347065dc50d414845fc7dada45dc0e..291c23618b5574de7402f710d7feba58b0edbcc2"
+}]
diff --git a/test/corpus/diff-summaries/ruby/ensure.json b/test/corpus/diff-summaries/ruby/ensure.json
new file mode 100644
index 000000000..e7b63e0ef
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/ensure.json
@@ -0,0 +1,270 @@
+[{
+ "testCaseDescription": "ruby-ensure-setup-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index e69de29..dbcd28c 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -0,0 +1,3 @@",
+ "+begin",
+ "+ foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "f6f1229dfdaa0bf7f5b33425764b3b4423e6e28c..b10ccba8ad4f11f74e74fe5eca3b97e5a604aff2"
+}
+,{
+ "testCaseDescription": "ruby-ensure-insert-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ }
+ },
+ "summary": "Added an ensure block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index dbcd28c..4332810 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -1,3 +1,4 @@",
+ " begin",
+ " foo",
+ "+ensure",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "b10ccba8ad4f11f74e74fe5eca3b97e5a604aff2..fa5e430655c2dcff9f8c706046b6c5a230172103"
+}
+,{
+ "testCaseDescription": "ruby-ensure-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ },
+ {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced an ensure block with an 'bar' identifier in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index 4332810..ddde828 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -1,4 +1,5 @@",
+ " begin",
+ " foo",
+ " ensure",
+ "+ bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "fa5e430655c2dcff9f8c706046b6c5a230172103..5eb9ced9edc1f64762468d4378055a3c44c7688c"
+}
+,{
+ "testCaseDescription": "ruby-ensure-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ },
+ {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'bar' identifier with the ensure block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index ddde828..4332810 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -1,5 +1,4 @@",
+ " begin",
+ " foo",
+ " ensure",
+ "- bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "5eb9ced9edc1f64762468d4378055a3c44c7688c..a8e6dd4fff6bf1580be14213e216207ed53cf059"
+}
+,{
+ "testCaseDescription": "ruby-ensure-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted an ensure block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index 4332810..dbcd28c 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -1,4 +1,3 @@",
+ " begin",
+ " foo",
+ "-ensure",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "a8e6dd4fff6bf1580be14213e216207ed53cf059..324595aac765613b219d4e80d627e6eb186cec57"
+}
+,{
+ "testCaseDescription": "ruby-ensure-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index dbcd28c..e69de29 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -1,3 +0,0 @@",
+ "-begin",
+ "- foo",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "324595aac765613b219d4e80d627e6eb186cec57..5df8bfbe172193e6124da27f457fa6fb19547593"
+}]
diff --git a/test/corpus/diff-summaries/ruby/for.json b/test/corpus/diff-summaries/ruby/for.json
index 19ea9c7f7..47c94908b 100644
--- a/test/corpus/diff-summaries/ruby/for.json
+++ b/test/corpus/diff-summaries/ruby/for.json
@@ -25,9 +25,18 @@
"filePaths": [
"for.rb"
],
- "sha1": "82fa376f02abeb45af195e210cd5cee82ab00f07",
+ "patch": [
+ "diff --git a/for.rb b/for.rb",
+ "index e69de29..e4ea259 100644",
+ "--- a/for.rb",
+ "+++ b/for.rb",
+ "@@ -0,0 +1,3 @@",
+ "+for x in y",
+ "+ f",
+ "+end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "96215e090bed74f6afb6545cded29cd5dd1b8104"
+ "shas": "b8e7a4d5034214328f3391e3c6001076f5bb6ec9..1e4b5ce7ca850c42c111c21fd9d8f38990fc3cbf"
}
,{
"testCaseDescription": "ruby-for-replacement-insert-test",
@@ -71,9 +80,24 @@
"filePaths": [
"for.rb"
],
- "sha1": "96215e090bed74f6afb6545cded29cd5dd1b8104",
+ "patch": [
+ "diff --git a/for.rb b/for.rb",
+ "index e4ea259..1ec5fb3 100644",
+ "--- a/for.rb",
+ "+++ b/for.rb",
+ "@@ -1,3 +1,9 @@",
+ "+for i in [1,2,3] do",
+ "+ print i",
+ "+end",
+ "+for x in y",
+ "+ f",
+ "+end",
+ " for x in y",
+ " f",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "d50d94b2571fc6b70d210dcf210196e96a38dd1d"
+ "shas": "1e4b5ce7ca850c42c111c21fd9d8f38990fc3cbf..c2e6812edb506dd8a3b9419e33f6d21c4998a1b7"
}
,{
"testCaseDescription": "ruby-for-delete-insert-test",
@@ -114,9 +138,22 @@
"filePaths": [
"for.rb"
],
- "sha1": "d50d94b2571fc6b70d210dcf210196e96a38dd1d",
+ "patch": [
+ "diff --git a/for.rb b/for.rb",
+ "index 1ec5fb3..b6b5bdd 100644",
+ "--- a/for.rb",
+ "+++ b/for.rb",
+ "@@ -1,5 +1,5 @@",
+ "-for i in [1,2,3] do",
+ "- print i",
+ "+for x in y",
+ "+ f",
+ " end",
+ " for x in y",
+ " f"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "fea9255406ce4c7e5ece0e1af17d1691d353edc1"
+ "shas": "c2e6812edb506dd8a3b9419e33f6d21c4998a1b7..bd3974e67a2154631e5a3348a1c4d13d38277cf7"
}
,{
"testCaseDescription": "ruby-for-replacement-test",
@@ -157,9 +194,22 @@
"filePaths": [
"for.rb"
],
- "sha1": "fea9255406ce4c7e5ece0e1af17d1691d353edc1",
+ "patch": [
+ "diff --git a/for.rb b/for.rb",
+ "index b6b5bdd..1ec5fb3 100644",
+ "--- a/for.rb",
+ "+++ b/for.rb",
+ "@@ -1,5 +1,5 @@",
+ "-for x in y",
+ "- f",
+ "+for i in [1,2,3] do",
+ "+ print i",
+ " end",
+ " for x in y",
+ " f"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "56923ddea441f6eaf01dd1834c9bf8340670a062"
+ "shas": "bd3974e67a2154631e5a3348a1c4d13d38277cf7..7547579e6c4c271afb05ba08271f0ed4b4b678ea"
}
,{
"testCaseDescription": "ruby-for-delete-replacement-test",
@@ -218,9 +268,26 @@
"filePaths": [
"for.rb"
],
- "sha1": "56923ddea441f6eaf01dd1834c9bf8340670a062",
+ "patch": [
+ "diff --git a/for.rb b/for.rb",
+ "index 1ec5fb3..543a0c8 100644",
+ "--- a/for.rb",
+ "+++ b/for.rb",
+ "@@ -1,9 +1,6 @@",
+ "-for i in [1,2,3] do",
+ "- print i",
+ "-end",
+ " for x in y",
+ " f",
+ " end",
+ "-for x in y",
+ "- f",
+ "+for i in [1,2,3] do",
+ "+ print i",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "65fe66fe0c3c7f3659e906f1eb3a6ca6188ba1e8"
+ "shas": "7547579e6c4c271afb05ba08271f0ed4b4b678ea..467953257426ae06a5f6026a93d2820676c903c0"
}
,{
"testCaseDescription": "ruby-for-delete-test",
@@ -249,9 +316,21 @@
"filePaths": [
"for.rb"
],
- "sha1": "65fe66fe0c3c7f3659e906f1eb3a6ca6188ba1e8",
+ "patch": [
+ "diff --git a/for.rb b/for.rb",
+ "index 543a0c8..9031ee4 100644",
+ "--- a/for.rb",
+ "+++ b/for.rb",
+ "@@ -1,6 +1,3 @@",
+ "-for x in y",
+ "- f",
+ "-end",
+ " for i in [1,2,3] do",
+ " print i",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "a0f366e07e9c13c7bdb7d414d48d3ef3838433e6"
+ "shas": "467953257426ae06a5f6026a93d2820676c903c0..1fd6b5413c62cdb0f0b1822736dfdacdbbc267a0"
}
,{
"testCaseDescription": "ruby-for-delete-rest-test",
@@ -280,7 +359,16 @@
"filePaths": [
"for.rb"
],
- "sha1": "a0f366e07e9c13c7bdb7d414d48d3ef3838433e6",
+ "patch": [
+ "diff --git a/for.rb b/for.rb",
+ "index 9031ee4..e69de29 100644",
+ "--- a/for.rb",
+ "+++ b/for.rb",
+ "@@ -1,3 +0,0 @@",
+ "-for i in [1,2,3] do",
+ "- print i",
+ "-end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "6bef099d2af7b41f171358e66662163cdf0bc96e"
+ "shas": "1fd6b5413c62cdb0f0b1822736dfdacdbbc267a0..72f935172c31da7ddd21bf1a12c7baeb4fdb3419"
}]
diff --git a/test/corpus/diff-summaries/ruby/hash.json b/test/corpus/diff-summaries/ruby/hash.json
index 12dd74495..6e9682bcc 100644
--- a/test/corpus/diff-summaries/ruby/hash.json
+++ b/test/corpus/diff-summaries/ruby/hash.json
@@ -25,9 +25,16 @@
"filePaths": [
"hash.rb"
],
- "sha1": "625fb3deaae6820d70e1d8cfe393b3d0c19484ff",
+ "patch": [
+ "diff --git a/hash.rb b/hash.rb",
+ "index e69de29..925618f 100644",
+ "--- a/hash.rb",
+ "+++ b/hash.rb",
+ "@@ -0,0 +1 @@",
+ "+{ :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "772b3a5b2f946cafcde59cc408bf4fb10403220a"
+ "shas": "bcd6d0b339d47a3a232e595d43db61acf2bfae04..1618b6749dab1997b0e6606829f8594c205b0616"
}
,{
"testCaseDescription": "ruby-hash-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"hash.rb"
],
- "sha1": "772b3a5b2f946cafcde59cc408bf4fb10403220a",
+ "patch": [
+ "diff --git a/hash.rb b/hash.rb",
+ "index 925618f..a0c7d41 100644",
+ "--- a/hash.rb",
+ "+++ b/hash.rb",
+ "@@ -1 +1,3 @@",
+ "+{ key1: \"changed value\", key2: 2, key3: true }",
+ "+{ :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }",
+ " { :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "9236ba7f889e6adeea78ca6d2bf6a9d1484c4de5"
+ "shas": "1618b6749dab1997b0e6606829f8594c205b0616..06de914a4e27ab3c14240b993c16ca75ea2a9f74"
}
,{
"testCaseDescription": "ruby-hash-delete-insert-test",
@@ -186,9 +202,19 @@
"filePaths": [
"hash.rb"
],
- "sha1": "9236ba7f889e6adeea78ca6d2bf6a9d1484c4de5",
+ "patch": [
+ "diff --git a/hash.rb b/hash.rb",
+ "index a0c7d41..d4ed2ec 100644",
+ "--- a/hash.rb",
+ "+++ b/hash.rb",
+ "@@ -1,3 +1,3 @@",
+ "-{ key1: \"changed value\", key2: 2, key3: true }",
+ "+{ :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }",
+ " { :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }",
+ " { :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "fb99ecf8de7a77d6af01ac7dafd2608c9b3350c5"
+ "shas": "06de914a4e27ab3c14240b993c16ca75ea2a9f74..9b4b4ff04981427a62802545d093e8536fe6b273"
}
,{
"testCaseDescription": "ruby-hash-replacement-test",
@@ -301,9 +327,19 @@
"filePaths": [
"hash.rb"
],
- "sha1": "fb99ecf8de7a77d6af01ac7dafd2608c9b3350c5",
+ "patch": [
+ "diff --git a/hash.rb b/hash.rb",
+ "index d4ed2ec..a0c7d41 100644",
+ "--- a/hash.rb",
+ "+++ b/hash.rb",
+ "@@ -1,3 +1,3 @@",
+ "-{ :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }",
+ "+{ key1: \"changed value\", key2: 2, key3: true }",
+ " { :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }",
+ " { :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "33fe30a86061a31b6c1d366d58704ccd2dc8d9c9"
+ "shas": "9b4b4ff04981427a62802545d093e8536fe6b273..35db7ac0f6000c8534941e46f08790624d929444"
}
,{
"testCaseDescription": "ruby-hash-delete-replacement-test",
@@ -362,9 +398,19 @@
"filePaths": [
"hash.rb"
],
- "sha1": "33fe30a86061a31b6c1d366d58704ccd2dc8d9c9",
+ "patch": [
+ "diff --git a/hash.rb b/hash.rb",
+ "index a0c7d41..4154b7d 100644",
+ "--- a/hash.rb",
+ "+++ b/hash.rb",
+ "@@ -1,3 +1,2 @@",
+ "-{ key1: \"changed value\", key2: 2, key3: true }",
+ "-{ :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }",
+ " { :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }",
+ "+{ key1: \"changed value\", key2: 2, key3: true }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "91d2b531eacbc7e98bd55a9f22afc7013d4e7119"
+ "shas": "35db7ac0f6000c8534941e46f08790624d929444..673381f3ce87fd2d1102e55ce01a719ac28ad4b1"
}
,{
"testCaseDescription": "ruby-hash-delete-test",
@@ -393,9 +439,17 @@
"filePaths": [
"hash.rb"
],
- "sha1": "91d2b531eacbc7e98bd55a9f22afc7013d4e7119",
+ "patch": [
+ "diff --git a/hash.rb b/hash.rb",
+ "index 4154b7d..4a0e8d0 100644",
+ "--- a/hash.rb",
+ "+++ b/hash.rb",
+ "@@ -1,2 +1 @@",
+ "-{ :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }",
+ " { key1: \"changed value\", key2: 2, key3: true }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "28a4aaf9ef28a5a41260138f70599d2cbcb12e23"
+ "shas": "673381f3ce87fd2d1102e55ce01a719ac28ad4b1..cba8ccf48ee9899a1c5ad781289fe52f129f48d4"
}
,{
"testCaseDescription": "ruby-hash-delete-rest-test",
@@ -424,7 +478,14 @@
"filePaths": [
"hash.rb"
],
- "sha1": "28a4aaf9ef28a5a41260138f70599d2cbcb12e23",
+ "patch": [
+ "diff --git a/hash.rb b/hash.rb",
+ "index 4a0e8d0..e69de29 100644",
+ "--- a/hash.rb",
+ "+++ b/hash.rb",
+ "@@ -1 +0,0 @@",
+ "-{ key1: \"changed value\", key2: 2, key3: true }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "0ba58b06e96f1b3ae8331ee4f06e4087a13c29f5"
+ "shas": "cba8ccf48ee9899a1c5ad781289fe52f129f48d4..5b279526f66afb77b2588f5173ce44d7cc693f97"
}]
diff --git a/test/corpus/diff-summaries/ruby/if-unless-modifiers.json b/test/corpus/diff-summaries/ruby/if-unless-modifiers.json
index 9b16e2d58..3698af040 100644
--- a/test/corpus/diff-summaries/ruby/if-unless-modifiers.json
+++ b/test/corpus/diff-summaries/ruby/if-unless-modifiers.json
@@ -25,9 +25,16 @@
"filePaths": [
"if-unless-modifiers.rb"
],
- "sha1": "9dee69155ea3541370dce7da3a81e7d3940e2317",
+ "patch": [
+ "diff --git a/if-unless-modifiers.rb b/if-unless-modifiers.rb",
+ "index e69de29..45ff4a6 100644",
+ "--- a/if-unless-modifiers.rb",
+ "+++ b/if-unless-modifiers.rb",
+ "@@ -0,0 +1 @@",
+ "+print unless foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "72f62c263b483fb808e30e70899c7ede343aa21a"
+ "shas": "4e2fff03bd38fd80461d8cac1a09c40ca80b2390..a156c775baf7ff53bfebb34f0b044ceca96516e0"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"if-unless-modifiers.rb"
],
- "sha1": "72f62c263b483fb808e30e70899c7ede343aa21a",
+ "patch": [
+ "diff --git a/if-unless-modifiers.rb b/if-unless-modifiers.rb",
+ "index 45ff4a6..cb2925a 100644",
+ "--- a/if-unless-modifiers.rb",
+ "+++ b/if-unless-modifiers.rb",
+ "@@ -1 +1,3 @@",
+ "+print if foo",
+ "+print unless foo",
+ " print unless foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "8b50beca01ac6324a87702756e9173f869abaf01"
+ "shas": "a156c775baf7ff53bfebb34f0b044ceca96516e0..935c4f046aca16b663c3b7bbf15bb4e3b89df95f"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-insert-test",
@@ -117,9 +133,19 @@
"filePaths": [
"if-unless-modifiers.rb"
],
- "sha1": "8b50beca01ac6324a87702756e9173f869abaf01",
+ "patch": [
+ "diff --git a/if-unless-modifiers.rb b/if-unless-modifiers.rb",
+ "index cb2925a..04f425e 100644",
+ "--- a/if-unless-modifiers.rb",
+ "+++ b/if-unless-modifiers.rb",
+ "@@ -1,3 +1,3 @@",
+ "-print if foo",
+ "+print unless foo",
+ " print unless foo",
+ " print unless foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "85c98a0fb367a029d93b2e50f0856798fe0e98f9"
+ "shas": "935c4f046aca16b663c3b7bbf15bb4e3b89df95f..2f5c75839c978eb166b5ce29ddcb0c663222be8e"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-replacement-test",
@@ -163,9 +189,19 @@
"filePaths": [
"if-unless-modifiers.rb"
],
- "sha1": "85c98a0fb367a029d93b2e50f0856798fe0e98f9",
+ "patch": [
+ "diff --git a/if-unless-modifiers.rb b/if-unless-modifiers.rb",
+ "index 04f425e..cb2925a 100644",
+ "--- a/if-unless-modifiers.rb",
+ "+++ b/if-unless-modifiers.rb",
+ "@@ -1,3 +1,3 @@",
+ "-print unless foo",
+ "+print if foo",
+ " print unless foo",
+ " print unless foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "4e4583f4d47d9c902d6e76a35a4bae3bb3ff0ed9"
+ "shas": "2f5c75839c978eb166b5ce29ddcb0c663222be8e..85ce995a212ec872107b09fd0baba8b62286c999"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-replacement-test",
@@ -224,9 +260,19 @@
"filePaths": [
"if-unless-modifiers.rb"
],
- "sha1": "4e4583f4d47d9c902d6e76a35a4bae3bb3ff0ed9",
+ "patch": [
+ "diff --git a/if-unless-modifiers.rb b/if-unless-modifiers.rb",
+ "index cb2925a..a3f9060 100644",
+ "--- a/if-unless-modifiers.rb",
+ "+++ b/if-unless-modifiers.rb",
+ "@@ -1,3 +1,2 @@",
+ "-print if foo",
+ "-print unless foo",
+ " print unless foo",
+ "+print if foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "c313e07c30cad4476f4de300adc660c1170cf609"
+ "shas": "85ce995a212ec872107b09fd0baba8b62286c999..38fd6b10133d898160cd44223c081010ca440b6f"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-test",
@@ -255,9 +301,17 @@
"filePaths": [
"if-unless-modifiers.rb"
],
- "sha1": "c313e07c30cad4476f4de300adc660c1170cf609",
+ "patch": [
+ "diff --git a/if-unless-modifiers.rb b/if-unless-modifiers.rb",
+ "index a3f9060..2021b1b 100644",
+ "--- a/if-unless-modifiers.rb",
+ "+++ b/if-unless-modifiers.rb",
+ "@@ -1,2 +1 @@",
+ "-print unless foo",
+ " print if foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "fefa947a4ade45d9762ebeea79f8db98ca51d9fb"
+ "shas": "38fd6b10133d898160cd44223c081010ca440b6f..52722842753439887074cefb1075c6a31015bc82"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-rest-test",
@@ -286,7 +340,14 @@
"filePaths": [
"if-unless-modifiers.rb"
],
- "sha1": "fefa947a4ade45d9762ebeea79f8db98ca51d9fb",
+ "patch": [
+ "diff --git a/if-unless-modifiers.rb b/if-unless-modifiers.rb",
+ "index 2021b1b..e69de29 100644",
+ "--- a/if-unless-modifiers.rb",
+ "+++ b/if-unless-modifiers.rb",
+ "@@ -1 +0,0 @@",
+ "-print if foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "f9e62bf41467cae8ada35780dd97dbbbddf57da5"
+ "shas": "52722842753439887074cefb1075c6a31015bc82..c7d3f438c72d2ab2a09e3fa47ba1cf9b175d2a9b"
}]
diff --git a/test/corpus/diff-summaries/ruby/if.json b/test/corpus/diff-summaries/ruby/if.json
index af2396f51..21bb283ca 100644
--- a/test/corpus/diff-summaries/ruby/if.json
+++ b/test/corpus/diff-summaries/ruby/if.json
@@ -25,9 +25,22 @@
"filePaths": [
"if.rb"
],
- "sha1": "03b2db1cb47a50501b36faf7fc35ebd3347c0a0a",
+ "patch": [
+ "diff --git a/if.rb b/if.rb",
+ "index e69de29..c4c729f 100644",
+ "--- a/if.rb",
+ "+++ b/if.rb",
+ "@@ -0,0 +1,7 @@",
+ "+if foo",
+ "+ bar",
+ "+elsif quux",
+ "+ baz",
+ "+else",
+ "+ bat",
+ "+end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "06f67f854a8c5278a30c80ea8daab16114f0705d"
+ "shas": "51729c359e350d71395532126c23bfed960f2373..eb8e4745aa2692c20519254d7b8d27b3a2c07cac"
}
,{
"testCaseDescription": "ruby-if-replacement-insert-test",
@@ -86,9 +99,29 @@
"filePaths": [
"if.rb"
],
- "sha1": "06f67f854a8c5278a30c80ea8daab16114f0705d",
+ "patch": [
+ "diff --git a/if.rb b/if.rb",
+ "index c4c729f..326833f 100644",
+ "--- a/if.rb",
+ "+++ b/if.rb",
+ "@@ -1,3 +1,14 @@",
+ "+if x",
+ "+end",
+ "+if y then",
+ "+end",
+ "+if foo",
+ "+ bar",
+ "+elsif quux",
+ "+ baz",
+ "+else",
+ "+ bat",
+ "+end",
+ " if foo",
+ " bar",
+ " elsif quux"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "c2e0eaba62e5fb53f9dd334f0e21b52064b27c6e"
+ "shas": "eb8e4745aa2692c20519254d7b8d27b3a2c07cac..a0d707f1e50df11d0aa4d3407dfcf79fad65acc6"
}
,{
"testCaseDescription": "ruby-if-delete-insert-test",
@@ -120,64 +153,37 @@
}
]
},
- "summary": "Replaced the 'x' identifier with the 'foo' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 5
- ],
- "end": [
- 2,
- 1
- ]
- },
- {
- "start": [
- 2,
- 3
- ],
- "end": [
- 2,
- 6
- ]
- }
- ]
- },
- "summary": "Replaced the '\n' expression statements with the 'bar' identifier"
+ "summary": "Replaced the 'x' identifier with the 'foo' identifier in the 'foo' if statement"
},
{
"span": {
"insert": {
"start": [
- 3,
- 7
- ],
- "end": [
- 3,
- 11
- ]
- }
- },
- "summary": "Added the 'quux' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
6
]
}
},
- "summary": "Added the 'baz' identifier"
+ "summary": "Added the 'bar' identifier in the 'foo' if statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 1
+ ]
+ }
+ },
+ "summary": "Added the 'quux' elsif block in the 'foo' if statement"
},
{
"span": {
@@ -192,7 +198,7 @@
]
}
},
- "summary": "Added the 'bat' identifier"
+ "summary": "Added the 'bat' identifier in the 'foo' if statement"
},
{
"span": {
@@ -216,9 +222,27 @@
"filePaths": [
"if.rb"
],
- "sha1": "c2e0eaba62e5fb53f9dd334f0e21b52064b27c6e",
+ "patch": [
+ "diff --git a/if.rb b/if.rb",
+ "index 326833f..2cbbfda 100644",
+ "--- a/if.rb",
+ "+++ b/if.rb",
+ "@@ -1,6 +1,9 @@",
+ "-if x",
+ "-end",
+ "-if y then",
+ "+if foo",
+ "+ bar",
+ "+elsif quux",
+ "+ baz",
+ "+else",
+ "+ bat",
+ " end",
+ " if foo",
+ " bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "321cfe0b9283c0b1f35c175e8259043b7f3fbc21"
+ "shas": "a0d707f1e50df11d0aa4d3407dfcf79fad65acc6..b9ef26ef27b3cf5ad0e522a145ede60f9b4f3dc2"
}
,{
"testCaseDescription": "ruby-if-replacement-test",
@@ -250,64 +274,37 @@
}
]
},
- "summary": "Replaced the 'foo' identifier with the 'x' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 2,
- 3
- ],
- "end": [
- 2,
- 6
- ]
- },
- {
- "start": [
- 1,
- 5
- ],
- "end": [
- 2,
- 1
- ]
- }
- ]
- },
- "summary": "Replaced the 'bar' identifier with the '\n' expression statements"
+ "summary": "Replaced the 'foo' identifier with the 'x' identifier in the 'x' if statement"
},
{
"span": {
"delete": {
"start": [
- 3,
- 7
- ],
- "end": [
- 3,
- 11
- ]
- }
- },
- "summary": "Deleted the 'quux' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
6
]
}
},
- "summary": "Deleted the 'baz' identifier"
+ "summary": "Deleted the 'bar' identifier in the 'x' if statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the 'quux' elsif block in the 'x' if statement"
},
{
"span": {
@@ -322,7 +319,7 @@
]
}
},
- "summary": "Deleted the 'bat' identifier"
+ "summary": "Deleted the 'bat' identifier in the 'x' if statement"
},
{
"span": {
@@ -346,9 +343,27 @@
"filePaths": [
"if.rb"
],
- "sha1": "321cfe0b9283c0b1f35c175e8259043b7f3fbc21",
+ "patch": [
+ "diff --git a/if.rb b/if.rb",
+ "index 2cbbfda..326833f 100644",
+ "--- a/if.rb",
+ "+++ b/if.rb",
+ "@@ -1,9 +1,6 @@",
+ "-if foo",
+ "- bar",
+ "-elsif quux",
+ "- baz",
+ "-else",
+ "- bat",
+ "+if x",
+ "+end",
+ "+if y then",
+ " end",
+ " if foo",
+ " bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "2eadf498c21757333d25f7c003b41afbe0579757"
+ "shas": "b9ef26ef27b3cf5ad0e522a145ede60f9b4f3dc2..af72ae7656106dce11ffcbd6c2a31e9a756b0342"
}
,{
"testCaseDescription": "ruby-if-delete-replacement-test",
@@ -377,9 +392,36 @@
"filePaths": [
"if.rb"
],
- "sha1": "2eadf498c21757333d25f7c003b41afbe0579757",
+ "patch": [
+ "diff --git a/if.rb b/if.rb",
+ "index 326833f..2927cc0 100644",
+ "--- a/if.rb",
+ "+++ b/if.rb",
+ "@@ -1,7 +1,3 @@",
+ "-if x",
+ "-end",
+ "-if y then",
+ "-end",
+ " if foo",
+ " bar",
+ " elsif quux",
+ "@@ -9,10 +5,7 @@ elsif quux",
+ " else",
+ " bat",
+ " end",
+ "-if foo",
+ "- bar",
+ "-elsif quux",
+ "- baz",
+ "-else",
+ "- bat",
+ "+if x",
+ "+end",
+ "+if y then",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "350fc0e2ea2916667a35b82f86f52cdcc479ff18"
+ "shas": "af72ae7656106dce11ffcbd6c2a31e9a756b0342..2aef901d538d790e42fec0a2a6b1522d8b4fce9e"
}
,{
"testCaseDescription": "ruby-if-delete-test",
@@ -408,9 +450,25 @@
"filePaths": [
"if.rb"
],
- "sha1": "350fc0e2ea2916667a35b82f86f52cdcc479ff18",
+ "patch": [
+ "diff --git a/if.rb b/if.rb",
+ "index 2927cc0..5bfb167 100644",
+ "--- a/if.rb",
+ "+++ b/if.rb",
+ "@@ -1,10 +1,3 @@",
+ "-if foo",
+ "- bar",
+ "-elsif quux",
+ "- baz",
+ "-else",
+ "- bat",
+ "-end",
+ " if x",
+ " end",
+ " if y then"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "0a4501920cccb75d37d857ed92b235778d943997"
+ "shas": "2aef901d538d790e42fec0a2a6b1522d8b4fce9e..bd1fd56e20054df058e8bc8d3e2dd0d523ecce08"
}
,{
"testCaseDescription": "ruby-if-delete-rest-test",
@@ -454,7 +512,17 @@
"filePaths": [
"if.rb"
],
- "sha1": "0a4501920cccb75d37d857ed92b235778d943997",
+ "patch": [
+ "diff --git a/if.rb b/if.rb",
+ "index 5bfb167..e69de29 100644",
+ "--- a/if.rb",
+ "+++ b/if.rb",
+ "@@ -1,4 +0,0 @@",
+ "-if x",
+ "-end",
+ "-if y then",
+ "-end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "482d92220765ab9cc71c4a13b264d98554a987b2"
+ "shas": "bd1fd56e20054df058e8bc8d3e2dd0d523ecce08..4fed48f0abf8058f93dbb4c7361358c434c9bb6d"
}]
diff --git a/test/corpus/diff-summaries/ruby/interpolation.json b/test/corpus/diff-summaries/ruby/interpolation.json
index 95054416b..fa27c2ce2 100644
--- a/test/corpus/diff-summaries/ruby/interpolation.json
+++ b/test/corpus/diff-summaries/ruby/interpolation.json
@@ -2,7 +2,7 @@
"testCaseDescription": "ruby-interpolation-insert-test",
"expectedResult": {
"changes": {
- "symbol.rb": [
+ "interpolation.rb": [
{
"span": {
"insert": {
@@ -38,17 +38,25 @@
"errors": {}
},
"filePaths": [
- "symbol.rb"
+ "interpolation.rb"
+ ],
+ "patch": [
+ "diff --git a/interpolation.rb b/interpolation.rb",
+ "index e69de29..a37ad45 100644",
+ "--- a/interpolation.rb",
+ "+++ b/interpolation.rb",
+ "@@ -0,0 +1,2 @@",
+ "+:\"foo #{bar}\"",
+ "+\"foo #{bar}\""
],
- "sha1": "27c8bb9ed1adb160824505aa87bcb49fd2bd0606",
"gitDir": "test/corpus/repos/ruby",
- "sha2": "7012caec8c5c7e9162e2fb6ca8e3a56137424389"
+ "shas": "2505617f30ca311da1378227cbf6a13d83647b91..ba6045bb44bd3872e04f0e0c67e330b73429defa"
}
,{
"testCaseDescription": "ruby-interpolation-replacement-insert-test",
"expectedResult": {
"changes": {
- "symbol.rb": [
+ "interpolation.rb": [
{
"span": {
"insert": {
@@ -114,17 +122,29 @@
"errors": {}
},
"filePaths": [
- "symbol.rb"
+ "interpolation.rb"
+ ],
+ "patch": [
+ "diff --git a/interpolation.rb b/interpolation.rb",
+ "index a37ad45..c024bd6 100644",
+ "--- a/interpolation.rb",
+ "+++ b/interpolation.rb",
+ "@@ -1,2 +1,6 @@",
+ "+:\"bar #{foo}\"",
+ "+\"bar #{foo}\"",
+ "+:\"foo #{bar}\"",
+ "+\"foo #{bar}\"",
+ " :\"foo #{bar}\"",
+ " \"foo #{bar}\""
],
- "sha1": "7012caec8c5c7e9162e2fb6ca8e3a56137424389",
"gitDir": "test/corpus/repos/ruby",
- "sha2": "cdde49454606b1e206ac682ad6401813ec06216e"
+ "shas": "ba6045bb44bd3872e04f0e0c67e330b73429defa..9eab77466f1fc1d8a2ceaed51eab7b16159d2c4c"
}
,{
"testCaseDescription": "ruby-interpolation-delete-insert-test",
"expectedResult": {
"changes": {
- "symbol.rb": [
+ "interpolation.rb": [
{
"span": {
"replace": [
@@ -184,17 +204,30 @@
"errors": {}
},
"filePaths": [
- "symbol.rb"
+ "interpolation.rb"
+ ],
+ "patch": [
+ "diff --git a/interpolation.rb b/interpolation.rb",
+ "index c024bd6..ce70dd5 100644",
+ "--- a/interpolation.rb",
+ "+++ b/interpolation.rb",
+ "@@ -1,5 +1,5 @@",
+ "-:\"bar #{foo}\"",
+ "-\"bar #{foo}\"",
+ "+:\"foo #{bar}\"",
+ "+\"foo #{bar}\"",
+ " :\"foo #{bar}\"",
+ " \"foo #{bar}\"",
+ " :\"foo #{bar}\""
],
- "sha1": "cdde49454606b1e206ac682ad6401813ec06216e",
"gitDir": "test/corpus/repos/ruby",
- "sha2": "45a81347385633df6b063567d6971c6035ad1184"
+ "shas": "9eab77466f1fc1d8a2ceaed51eab7b16159d2c4c..c23529986ecc8afd8cc26b6e54dc68f203488cd0"
}
,{
"testCaseDescription": "ruby-interpolation-replacement-test",
"expectedResult": {
"changes": {
- "symbol.rb": [
+ "interpolation.rb": [
{
"span": {
"replace": [
@@ -254,17 +287,30 @@
"errors": {}
},
"filePaths": [
- "symbol.rb"
+ "interpolation.rb"
+ ],
+ "patch": [
+ "diff --git a/interpolation.rb b/interpolation.rb",
+ "index ce70dd5..c024bd6 100644",
+ "--- a/interpolation.rb",
+ "+++ b/interpolation.rb",
+ "@@ -1,5 +1,5 @@",
+ "-:\"foo #{bar}\"",
+ "-\"foo #{bar}\"",
+ "+:\"bar #{foo}\"",
+ "+\"bar #{foo}\"",
+ " :\"foo #{bar}\"",
+ " \"foo #{bar}\"",
+ " :\"foo #{bar}\""
],
- "sha1": "45a81347385633df6b063567d6971c6035ad1184",
"gitDir": "test/corpus/repos/ruby",
- "sha2": "06b627b15c97b775ba5734a23c018630fb959cb4"
+ "shas": "c23529986ecc8afd8cc26b6e54dc68f203488cd0..477f525a5dd8fecc22f1eaaa4e77419e0255d2a9"
}
,{
"testCaseDescription": "ruby-interpolation-delete-replacement-test",
"expectedResult": {
"changes": {
- "symbol.rb": [
+ "interpolation.rb": [
{
"span": {
"delete": {
@@ -360,17 +406,31 @@
"errors": {}
},
"filePaths": [
- "symbol.rb"
+ "interpolation.rb"
+ ],
+ "patch": [
+ "diff --git a/interpolation.rb b/interpolation.rb",
+ "index c024bd6..f56366a 100644",
+ "--- a/interpolation.rb",
+ "+++ b/interpolation.rb",
+ "@@ -1,6 +1,4 @@",
+ "-:\"bar #{foo}\"",
+ "-\"bar #{foo}\"",
+ "-:\"foo #{bar}\"",
+ "-\"foo #{bar}\"",
+ " :\"foo #{bar}\"",
+ " \"foo #{bar}\"",
+ "+:\"bar #{foo}\"",
+ "+\"bar #{foo}\""
],
- "sha1": "06b627b15c97b775ba5734a23c018630fb959cb4",
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e8c88d21818c95eb56330219a546fe2b7d948709"
+ "shas": "477f525a5dd8fecc22f1eaaa4e77419e0255d2a9..c84f76f558cce919ec1935a75ad1b830b4511ff8"
}
,{
"testCaseDescription": "ruby-interpolation-delete-test",
"expectedResult": {
"changes": {
- "symbol.rb": [
+ "interpolation.rb": [
{
"span": {
"delete": {
@@ -406,17 +466,27 @@
"errors": {}
},
"filePaths": [
- "symbol.rb"
+ "interpolation.rb"
+ ],
+ "patch": [
+ "diff --git a/interpolation.rb b/interpolation.rb",
+ "index f56366a..9b7bb17 100644",
+ "--- a/interpolation.rb",
+ "+++ b/interpolation.rb",
+ "@@ -1,4 +1,2 @@",
+ "-:\"foo #{bar}\"",
+ "-\"foo #{bar}\"",
+ " :\"bar #{foo}\"",
+ " \"bar #{foo}\""
],
- "sha1": "e8c88d21818c95eb56330219a546fe2b7d948709",
"gitDir": "test/corpus/repos/ruby",
- "sha2": "a259650f6a8aefbbd8f41e70c0e12b13c19c9e1b"
+ "shas": "c84f76f558cce919ec1935a75ad1b830b4511ff8..cf1a6e3114fde76b4c1d6ad65ac4c2c10f3a2b3a"
}
,{
"testCaseDescription": "ruby-interpolation-delete-rest-test",
"expectedResult": {
"changes": {
- "symbol.rb": [
+ "interpolation.rb": [
{
"span": {
"delete": {
@@ -452,9 +522,17 @@
"errors": {}
},
"filePaths": [
- "symbol.rb"
+ "interpolation.rb"
+ ],
+ "patch": [
+ "diff --git a/interpolation.rb b/interpolation.rb",
+ "index 9b7bb17..e69de29 100644",
+ "--- a/interpolation.rb",
+ "+++ b/interpolation.rb",
+ "@@ -1,2 +0,0 @@",
+ "-:\"bar #{foo}\"",
+ "-\"bar #{foo}\""
],
- "sha1": "a259650f6a8aefbbd8f41e70c0e12b13c19c9e1b",
"gitDir": "test/corpus/repos/ruby",
- "sha2": "0de5663fae24bc6af3327776d01518ef6a240ed6"
+ "shas": "cf1a6e3114fde76b4c1d6ad65ac4c2c10f3a2b3a..ef8d34476c23317120bf744df9d41b9110a04c03"
}]
diff --git a/test/corpus/diff-summaries/ruby/lambda-dash-rocket.json b/test/corpus/diff-summaries/ruby/lambda-dash-rocket.json
index bd88f056c..f79d789f7 100644
--- a/test/corpus/diff-summaries/ruby/lambda-dash-rocket.json
+++ b/test/corpus/diff-summaries/ruby/lambda-dash-rocket.json
@@ -25,9 +25,19 @@
"filePaths": [
"lambda-dash-rocket.rb"
],
- "sha1": "bf01ed653791dfe5beb43e85c33f6e2d069fefc2",
+ "patch": [
+ "diff --git a/lambda-dash-rocket.rb b/lambda-dash-rocket.rb",
+ "index e69de29..87e5852 100644",
+ "--- a/lambda-dash-rocket.rb",
+ "+++ b/lambda-dash-rocket.rb",
+ "@@ -0,0 +1,4 @@",
+ "+-> (a, b, c) {",
+ "+ 1",
+ "+ 2",
+ "+}"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "f73764d7261d1e1170e691733b6b7c74132936a6"
+ "shas": "39e3abbd0e3332afc2314759fdd350cba39b8e28..39eba620219e1cc7172b218e7f7f4cc0b945515e"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-replacement-insert-test",
@@ -71,9 +81,23 @@
"filePaths": [
"lambda-dash-rocket.rb"
],
- "sha1": "f73764d7261d1e1170e691733b6b7c74132936a6",
+ "patch": [
+ "diff --git a/lambda-dash-rocket.rb b/lambda-dash-rocket.rb",
+ "index 87e5852..3daf118 100644",
+ "--- a/lambda-dash-rocket.rb",
+ "+++ b/lambda-dash-rocket.rb",
+ "@@ -1,3 +1,8 @@",
+ "+-> { foo }",
+ "+-> (a, b, c) {",
+ "+ 1",
+ "+ 2",
+ "+}",
+ " -> (a, b, c) {",
+ " 1",
+ " 2"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "a565bef62371853b9de3114627e035ff440fd605"
+ "shas": "39eba620219e1cc7172b218e7f7f4cc0b945515e..db5ebcd81ad82fbb223f7ba862191d01280823bd"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-insert-test",
@@ -114,9 +138,23 @@
"filePaths": [
"lambda-dash-rocket.rb"
],
- "sha1": "a565bef62371853b9de3114627e035ff440fd605",
+ "patch": [
+ "diff --git a/lambda-dash-rocket.rb b/lambda-dash-rocket.rb",
+ "index 3daf118..53ea219 100644",
+ "--- a/lambda-dash-rocket.rb",
+ "+++ b/lambda-dash-rocket.rb",
+ "@@ -1,4 +1,7 @@",
+ "--> { foo }",
+ "+-> (a, b, c) {",
+ "+ 1",
+ "+ 2",
+ "+}",
+ " -> (a, b, c) {",
+ " 1",
+ " 2"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "1dbde963827409f36b55fa0f88b86e8ff782d781"
+ "shas": "db5ebcd81ad82fbb223f7ba862191d01280823bd..f31ea619acedac7aafa78d4821e3359c29837a2e"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-replacement-test",
@@ -157,9 +195,23 @@
"filePaths": [
"lambda-dash-rocket.rb"
],
- "sha1": "1dbde963827409f36b55fa0f88b86e8ff782d781",
+ "patch": [
+ "diff --git a/lambda-dash-rocket.rb b/lambda-dash-rocket.rb",
+ "index 53ea219..3daf118 100644",
+ "--- a/lambda-dash-rocket.rb",
+ "+++ b/lambda-dash-rocket.rb",
+ "@@ -1,7 +1,4 @@",
+ "--> (a, b, c) {",
+ "- 1",
+ "- 2",
+ "-}",
+ "+-> { foo }",
+ " -> (a, b, c) {",
+ " 1",
+ " 2"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "b64019a98f9d5d736aa8aee285c18f359f59ac54"
+ "shas": "f31ea619acedac7aafa78d4821e3359c29837a2e..78558177fbe1e8a9b635366d37dca7bc63c35a89"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-replacement-test",
@@ -218,9 +270,25 @@
"filePaths": [
"lambda-dash-rocket.rb"
],
- "sha1": "b64019a98f9d5d736aa8aee285c18f359f59ac54",
+ "patch": [
+ "diff --git a/lambda-dash-rocket.rb b/lambda-dash-rocket.rb",
+ "index 3daf118..5e26f49 100644",
+ "--- a/lambda-dash-rocket.rb",
+ "+++ b/lambda-dash-rocket.rb",
+ "@@ -1,9 +1,5 @@",
+ "--> { foo }",
+ "--> (a, b, c) {",
+ "- 1",
+ "- 2",
+ "-}",
+ " -> (a, b, c) {",
+ " 1",
+ " 2",
+ " }",
+ "+-> { foo }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "68d2b5640d198edce8cf79588d67c73b3c12bc22"
+ "shas": "78558177fbe1e8a9b635366d37dca7bc63c35a89..1b5da246d2f7c8e084437f516a1e0acef8a668b5"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-test",
@@ -249,9 +317,20 @@
"filePaths": [
"lambda-dash-rocket.rb"
],
- "sha1": "68d2b5640d198edce8cf79588d67c73b3c12bc22",
+ "patch": [
+ "diff --git a/lambda-dash-rocket.rb b/lambda-dash-rocket.rb",
+ "index 5e26f49..72c62f8 100644",
+ "--- a/lambda-dash-rocket.rb",
+ "+++ b/lambda-dash-rocket.rb",
+ "@@ -1,5 +1 @@",
+ "--> (a, b, c) {",
+ "- 1",
+ "- 2",
+ "-}",
+ " -> { foo }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "f2810ef2729cf5ab883af5d89e8e824a0b5d8c25"
+ "shas": "1b5da246d2f7c8e084437f516a1e0acef8a668b5..885c3dd4bc6b78521a51d05585cd3600901ebc5f"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-rest-test",
@@ -280,7 +359,14 @@
"filePaths": [
"lambda-dash-rocket.rb"
],
- "sha1": "f2810ef2729cf5ab883af5d89e8e824a0b5d8c25",
+ "patch": [
+ "diff --git a/lambda-dash-rocket.rb b/lambda-dash-rocket.rb",
+ "index 72c62f8..e69de29 100644",
+ "--- a/lambda-dash-rocket.rb",
+ "+++ b/lambda-dash-rocket.rb",
+ "@@ -1 +0,0 @@",
+ "--> { foo }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "2f2168edc8d0acbcdcf2e14df2188f727260ad2f"
+ "shas": "885c3dd4bc6b78521a51d05585cd3600901ebc5f..18022ae6ebbe9a88b3eaf0cfa0654e8f8bc5dd01"
}]
diff --git a/test/corpus/diff-summaries/ruby/lambda.json b/test/corpus/diff-summaries/ruby/lambda.json
index 32bb84f0a..d7b852692 100644
--- a/test/corpus/diff-summaries/ruby/lambda.json
+++ b/test/corpus/diff-summaries/ruby/lambda.json
@@ -25,9 +25,16 @@
"filePaths": [
"lambda.rb"
],
- "sha1": "2f2168edc8d0acbcdcf2e14df2188f727260ad2f",
+ "patch": [
+ "diff --git a/lambda.rb b/lambda.rb",
+ "index e69de29..943ace3 100644",
+ "--- a/lambda.rb",
+ "+++ b/lambda.rb",
+ "@@ -0,0 +1 @@",
+ "+lambda { foo }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "34efedfc02ab3c716d99aeccd997b511f934b59c"
+ "shas": "18022ae6ebbe9a88b3eaf0cfa0654e8f8bc5dd01..3056cfc87793da5967931201f46bc12dc4186bf5"
}
,{
"testCaseDescription": "ruby-lambda-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"lambda.rb"
],
- "sha1": "34efedfc02ab3c716d99aeccd997b511f934b59c",
+ "patch": [
+ "diff --git a/lambda.rb b/lambda.rb",
+ "index 943ace3..cb843af 100644",
+ "--- a/lambda.rb",
+ "+++ b/lambda.rb",
+ "@@ -1 +1,3 @@",
+ "+lambda { |x| x + 1 }",
+ "+lambda { foo }",
+ " lambda { foo }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "7fc22d4c0f96485547cd86ab5793a5ea5cf093e8"
+ "shas": "3056cfc87793da5967931201f46bc12dc4186bf5..a33da9171f4f363df081fa60a58279175ea6bbc7"
}
,{
"testCaseDescription": "ruby-lambda-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"lambda.rb"
],
- "sha1": "7fc22d4c0f96485547cd86ab5793a5ea5cf093e8",
+ "patch": [
+ "diff --git a/lambda.rb b/lambda.rb",
+ "index cb843af..447bfb7 100644",
+ "--- a/lambda.rb",
+ "+++ b/lambda.rb",
+ "@@ -1,3 +1,3 @@",
+ "-lambda { |x| x + 1 }",
+ "+lambda { foo }",
+ " lambda { foo }",
+ " lambda { foo }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "55cecf3f169734926d6bc2461f64f191846ed85b"
+ "shas": "a33da9171f4f363df081fa60a58279175ea6bbc7..e52658a62a6c3953d8382d0296c267b2a9a3b3dc"
}
,{
"testCaseDescription": "ruby-lambda-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"lambda.rb"
],
- "sha1": "55cecf3f169734926d6bc2461f64f191846ed85b",
+ "patch": [
+ "diff --git a/lambda.rb b/lambda.rb",
+ "index 447bfb7..cb843af 100644",
+ "--- a/lambda.rb",
+ "+++ b/lambda.rb",
+ "@@ -1,3 +1,3 @@",
+ "-lambda { foo }",
+ "+lambda { |x| x + 1 }",
+ " lambda { foo }",
+ " lambda { foo }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "742c346748fd07ef606771abb373819572a3a11c"
+ "shas": "e52658a62a6c3953d8382d0296c267b2a9a3b3dc..522cd601966aa3e9f5fc0f033f81cbefcd706669"
}
,{
"testCaseDescription": "ruby-lambda-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"lambda.rb"
],
- "sha1": "742c346748fd07ef606771abb373819572a3a11c",
+ "patch": [
+ "diff --git a/lambda.rb b/lambda.rb",
+ "index cb843af..4ebf1f8 100644",
+ "--- a/lambda.rb",
+ "+++ b/lambda.rb",
+ "@@ -1,3 +1,2 @@",
+ "-lambda { |x| x + 1 }",
+ "-lambda { foo }",
+ " lambda { foo }",
+ "+lambda { |x| x + 1 }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "7bcf126286a94ea339c4259efd6e09daf621614a"
+ "shas": "522cd601966aa3e9f5fc0f033f81cbefcd706669..1f004455547e75075f1c16f62433c080571f69ae"
}
,{
"testCaseDescription": "ruby-lambda-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"lambda.rb"
],
- "sha1": "7bcf126286a94ea339c4259efd6e09daf621614a",
+ "patch": [
+ "diff --git a/lambda.rb b/lambda.rb",
+ "index 4ebf1f8..dfe1b8b 100644",
+ "--- a/lambda.rb",
+ "+++ b/lambda.rb",
+ "@@ -1,2 +1 @@",
+ "-lambda { foo }",
+ " lambda { |x| x + 1 }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "3af2c38183a09d4b7136efccd201cc29a98b643e"
+ "shas": "1f004455547e75075f1c16f62433c080571f69ae..fb578efc5242fd49d72fc4e06e75adf0320ef31d"
}
,{
"testCaseDescription": "ruby-lambda-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"lambda.rb"
],
- "sha1": "3af2c38183a09d4b7136efccd201cc29a98b643e",
+ "patch": [
+ "diff --git a/lambda.rb b/lambda.rb",
+ "index dfe1b8b..e69de29 100644",
+ "--- a/lambda.rb",
+ "+++ b/lambda.rb",
+ "@@ -1 +0,0 @@",
+ "-lambda { |x| x + 1 }"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "82fa376f02abeb45af195e210cd5cee82ab00f07"
+ "shas": "fb578efc5242fd49d72fc4e06e75adf0320ef31d..b8e7a4d5034214328f3391e3c6001076f5bb6ec9"
}]
diff --git a/test/corpus/diff-summaries/ruby/math-assignment.json b/test/corpus/diff-summaries/ruby/math-assignment.json
index 4d2496b11..cb60eade9 100644
--- a/test/corpus/diff-summaries/ruby/math-assignment.json
+++ b/test/corpus/diff-summaries/ruby/math-assignment.json
@@ -85,9 +85,20 @@
"filePaths": [
"math-assignment.rb"
],
- "sha1": "644e721ee81af7e3491342e9ce3c03c31a55cfb7",
+ "patch": [
+ "diff --git a/math-assignment.rb b/math-assignment.rb",
+ "index e69de29..9c3bd32 100644",
+ "--- a/math-assignment.rb",
+ "+++ b/math-assignment.rb",
+ "@@ -0,0 +1,5 @@",
+ "+x += 1",
+ "+x -= 1",
+ "+x *= 1",
+ "+x /= 1",
+ "+x **= 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "b7dfa15d6187b14d18be50ccb795956af9147613"
+ "shas": "b8a1e5f549bc1fa5a1424093d499d32fa0987cee..5438892990d5ecfa57ee99c577aa175b73ffbabe"
}
,{
"testCaseDescription": "ruby-math-assignment-replacement-insert-test",
@@ -251,9 +262,28 @@
"filePaths": [
"math-assignment.rb"
],
- "sha1": "b7dfa15d6187b14d18be50ccb795956af9147613",
+ "patch": [
+ "diff --git a/math-assignment.rb b/math-assignment.rb",
+ "index 9c3bd32..ebf1cd7 100644",
+ "--- a/math-assignment.rb",
+ "+++ b/math-assignment.rb",
+ "@@ -1,3 +1,13 @@",
+ "+x+= 2",
+ "+x -= 1",
+ "+x *= 1",
+ "+x /= 1",
+ "+x **= 1",
+ "+x += 1",
+ "+x -= 1",
+ "+x *= 1",
+ "+x /= 1",
+ "+x **= 1",
+ " x += 1",
+ " x -= 1",
+ " x *= 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "4534512207149f194dd347f448d495c98f1b8eda"
+ "shas": "5438892990d5ecfa57ee99c577aa175b73ffbabe..f70cdf5d64b650094018ccee6d9b42009ad22fde"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-insert-test",
@@ -294,9 +324,20 @@
"filePaths": [
"math-assignment.rb"
],
- "sha1": "4534512207149f194dd347f448d495c98f1b8eda",
+ "patch": [
+ "diff --git a/math-assignment.rb b/math-assignment.rb",
+ "index ebf1cd7..8751768 100644",
+ "--- a/math-assignment.rb",
+ "+++ b/math-assignment.rb",
+ "@@ -1,4 +1,4 @@",
+ "-x+= 2",
+ "+x += 1",
+ " x -= 1",
+ " x *= 1",
+ " x /= 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "fb1f78bd03eaba84b56395e7438018543565a0d9"
+ "shas": "f70cdf5d64b650094018ccee6d9b42009ad22fde..e9c35072aff21a20a3e388f9cf3c172194218160"
}
,{
"testCaseDescription": "ruby-math-assignment-replacement-test",
@@ -337,9 +378,20 @@
"filePaths": [
"math-assignment.rb"
],
- "sha1": "fb1f78bd03eaba84b56395e7438018543565a0d9",
+ "patch": [
+ "diff --git a/math-assignment.rb b/math-assignment.rb",
+ "index 8751768..ebf1cd7 100644",
+ "--- a/math-assignment.rb",
+ "+++ b/math-assignment.rb",
+ "@@ -1,4 +1,4 @@",
+ "-x += 1",
+ "+x+= 2",
+ " x -= 1",
+ " x *= 1",
+ " x /= 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "ac1296999ccb9067af062d4d59e16513c61cd81d"
+ "shas": "e9c35072aff21a20a3e388f9cf3c172194218160..76a45dcf02f834864ade4b2ed1ec5fd0dd0c7f76"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-replacement-test",
@@ -458,9 +510,30 @@
"filePaths": [
"math-assignment.rb"
],
- "sha1": "ac1296999ccb9067af062d4d59e16513c61cd81d",
+ "patch": [
+ "diff --git a/math-assignment.rb b/math-assignment.rb",
+ "index ebf1cd7..207ee13 100644",
+ "--- a/math-assignment.rb",
+ "+++ b/math-assignment.rb",
+ "@@ -1,14 +1,9 @@",
+ "-x+= 2",
+ "-x -= 1",
+ "-x *= 1",
+ "-x /= 1",
+ "-x **= 1",
+ " x += 1",
+ " x -= 1",
+ " x *= 1",
+ " x /= 1",
+ " x **= 1",
+ "-x += 1",
+ "+x+= 2",
+ " x -= 1",
+ " x *= 1",
+ " x /= 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "25954da8e8e2b92da4d869668e380180773997d7"
+ "shas": "76a45dcf02f834864ade4b2ed1ec5fd0dd0c7f76..33f478735db5f9a23c2760a55dfc3e4acbdc46f8"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-test",
@@ -549,9 +622,23 @@
"filePaths": [
"math-assignment.rb"
],
- "sha1": "25954da8e8e2b92da4d869668e380180773997d7",
+ "patch": [
+ "diff --git a/math-assignment.rb b/math-assignment.rb",
+ "index 207ee13..fd6ee10 100644",
+ "--- a/math-assignment.rb",
+ "+++ b/math-assignment.rb",
+ "@@ -1,8 +1,3 @@",
+ "-x += 1",
+ "-x -= 1",
+ "-x *= 1",
+ "-x /= 1",
+ "-x **= 1",
+ " x+= 2",
+ " x -= 1",
+ " x *= 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "9a78372252901282e34c9f9ec376f3e4b4c761ce"
+ "shas": "33f478735db5f9a23c2760a55dfc3e4acbdc46f8..f81054ebeafb1e11c934903a5f5bc2341f79a500"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-rest-test",
@@ -640,7 +727,18 @@
"filePaths": [
"math-assignment.rb"
],
- "sha1": "9a78372252901282e34c9f9ec376f3e4b4c761ce",
+ "patch": [
+ "diff --git a/math-assignment.rb b/math-assignment.rb",
+ "index fd6ee10..e69de29 100644",
+ "--- a/math-assignment.rb",
+ "+++ b/math-assignment.rb",
+ "@@ -1,5 +0,0 @@",
+ "-x+= 2",
+ "-x -= 1",
+ "-x *= 1",
+ "-x /= 1",
+ "-x **= 1"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "d411db29ef77ddde028a6408d3e5b9d1af156598"
+ "shas": "f81054ebeafb1e11c934903a5f5bc2341f79a500..6564c9c8832540d910a4118a6130305613ef9772"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-calls.json b/test/corpus/diff-summaries/ruby/method-calls.json
new file mode 100644
index 000000000..9e91b4746
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/method-calls.json
@@ -0,0 +1,353 @@
+[{
+ "testCaseDescription": "ruby-method-calls-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'x.foo()' method call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index e69de29..5831d31 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -0,0 +1 @@",
+ "+x.foo()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "17903b081197a8af07c0566effcb951a5c2b4e92..e934fefb49abf087c33e1240f8f6dd8750461981"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar()' function call"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'x.foo()' method call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index 5831d31..ce891a7 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1 +1,3 @@",
+ "+bar()",
+ "+x.foo()",
+ " x.foo()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "e934fefb49abf087c33e1240f8f6dd8750461981..aa456894a021e11601d5c5545633e8f9391038a9"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'x.foo()' method call"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar()' function call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index ce891a7..472abf1 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1,3 +1,3 @@",
+ "-bar()",
+ "+x.foo()",
+ " x.foo()",
+ " x.foo()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "aa456894a021e11601d5c5545633e8f9391038a9..526f90542e5291bf410c4f56e69c47282675bd1c"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar()' function call"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'x.foo()' method call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index 472abf1..ce891a7 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1,3 +1,3 @@",
+ "-x.foo()",
+ "+bar()",
+ " x.foo()",
+ " x.foo()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "526f90542e5291bf410c4f56e69c47282675bd1c..7c5ce020e41d5b01f7ea9f88acf3386f426e01e6"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar()' function call"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'x.foo()' method call"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar()' function call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index ce891a7..6c5bbe0 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1,3 +1,2 @@",
+ "-bar()",
+ "-x.foo()",
+ " x.foo()",
+ "+bar()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "7c5ce020e41d5b01f7ea9f88acf3386f426e01e6..ee7be1e9e40189aa48d053b3891b9f9ad093db4e"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-delete-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'x.foo()' method call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index 6c5bbe0..4be2e26 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1,2 +1 @@",
+ "-x.foo()",
+ " bar()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "ee7be1e9e40189aa48d053b3891b9f9ad093db4e..beafe8aef216cb2b54edb534e94edb3fd5138052"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar()' function call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index 4be2e26..e69de29 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1 +0,0 @@",
+ "-bar()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "beafe8aef216cb2b54edb534e94edb3fd5138052..eb51a430951de620d64e6e92df9603e953708321"
+}]
diff --git a/test/corpus/diff-summaries/ruby/method-declaration-params.json b/test/corpus/diff-summaries/ruby/method-declaration-params.json
new file mode 100644
index 000000000..af40f0ba8
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/method-declaration-params.json
@@ -0,0 +1,268 @@
+[{
+ "testCaseDescription": "ruby-method-declaration-params-setup-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index e69de29..ff7bbbe 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -0,0 +1,2 @@",
+ "+def foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "f82bf4ad6ff1fbd5a9259bd1eacc5a0f4f859641..0197e7f75970a0d4fb4ac2094b70667322cd28f7"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-params-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 9
+ ],
+ "end": [
+ 1,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier in the 'foo(a)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index ff7bbbe..47fdd58 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -1,2 +1,2 @@",
+ "-def foo",
+ "+def foo(a)",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "0197e7f75970a0d4fb4ac2094b70667322cd28f7..552d3174c07720ca6e22d4d10793d77b8cbd8272"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-params-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 12
+ ],
+ "end": [
+ 1,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier in the 'foo(a, b, c)' method"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 15
+ ],
+ "end": [
+ 1,
+ 16
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier in the 'foo(a, b, c)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index 47fdd58..b9f1ab5 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -1,2 +1,2 @@",
+ "-def foo(a)",
+ "+def foo(a, b, c)",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "552d3174c07720ca6e22d4d10793d77b8cbd8272..d1de60658c07241f71d613af600c1182ae93d5ee"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-params-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 12
+ ],
+ "end": [
+ 1,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier in the 'foo(a)' method"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 15
+ ],
+ "end": [
+ 1,
+ 16
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier in the 'foo(a)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index b9f1ab5..47fdd58 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -1,2 +1,2 @@",
+ "-def foo(a, b, c)",
+ "+def foo(a)",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d1de60658c07241f71d613af600c1182ae93d5ee..9dbfbeb8ecb62a12415834b6b4d6acb2c25248e1"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-params-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 9
+ ],
+ "end": [
+ 1,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier in the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index 47fdd58..ff7bbbe 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -1,2 +1,2 @@",
+ "-def foo(a)",
+ "+def foo",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "9dbfbeb8ecb62a12415834b6b4d6acb2c25248e1..104d7b89ddba1700c8472a8622398479e4b75428"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-params-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index ff7bbbe..e69de29 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -1,2 +0,0 @@",
+ "-def foo",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "104d7b89ddba1700c8472a8622398479e4b75428..38847e533e9d63b067fd46b4e3bf8e4bcd68f0db"
+}]
diff --git a/test/corpus/diff-summaries/ruby/method-declaration.json b/test/corpus/diff-summaries/ruby/method-declaration.json
new file mode 100644
index 000000000..630fe1b89
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/method-declaration.json
@@ -0,0 +1,426 @@
+[{
+ "testCaseDescription": "ruby-method-declaration-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index e69de29..ff7bbbe 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -0,0 +1,2 @@",
+ "+def foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "431277d98db3b1763f33f0ad74712c0605d7f610..252774d5f106ebd96337b469288937b17174b5ef"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'bar(a)' method"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index ff7bbbe..fcc5a9b 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,2 +1,7 @@",
+ "+def bar(a)",
+ "+ baz",
+ "+end",
+ "+def foo",
+ "+end",
+ " def foo",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "252774d5f106ebd96337b469288937b17174b5ef..35a4b8fddb3dfdc3f6d554ff18bed1a54a7f555b"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'bar' identifier with the 'foo' identifier in the 'foo()' method"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 9
+ ],
+ "end": [
+ 1,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier in the 'foo()' method"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'baz' identifier in the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index fcc5a9b..a09a49a 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,5 +1,4 @@",
+ "-def bar(a)",
+ "- baz",
+ "+def foo",
+ " end",
+ " def foo",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "35a4b8fddb3dfdc3f6d554ff18bed1a54a7f555b..2ef30f177ed4748865fbf8341e8859a13a1addc1"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'foo' identifier with the 'bar' identifier in the 'bar(a)' method"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 9
+ ],
+ "end": [
+ 1,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier in the 'bar(a)' method"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'baz' identifier in the 'bar(a)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index a09a49a..fcc5a9b 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,4 +1,5 @@",
+ "-def foo",
+ "+def bar(a)",
+ "+ baz",
+ " end",
+ " def foo",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "2ef30f177ed4748865fbf8341e8859a13a1addc1..da07a93d19fb9f023e1e9f660ffa1838d6493b13"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar(a)' method"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo()' method"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'bar(a)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index fcc5a9b..14b3fc2 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,7 +1,5 @@",
+ "-def bar(a)",
+ "- baz",
+ "-end",
+ " def foo",
+ " end",
+ "-def foo",
+ "+def bar(a)",
+ "+ baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "da07a93d19fb9f023e1e9f660ffa1838d6493b13..1acebf2b365c8f3d9a79e60ac9fc196926633beb"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-delete-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index 14b3fc2..d90f5cf 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,5 +1,3 @@",
+ "-def foo",
+ "-end",
+ " def bar(a)",
+ " baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1acebf2b365c8f3d9a79e60ac9fc196926633beb..dc91b88e86820f5cb807a7219c5fb0b1351be372"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar(a)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index d90f5cf..e69de29 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,3 +0,0 @@",
+ "-def bar(a)",
+ "- baz",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "dc91b88e86820f5cb807a7219c5fb0b1351be372..f82bf4ad6ff1fbd5a9259bd1eacc5a0f4f859641"
+}]
diff --git a/test/corpus/diff-summaries/ruby/method-invocation.json b/test/corpus/diff-summaries/ruby/method-invocation.json
index 618893401..ae254a071 100644
--- a/test/corpus/diff-summaries/ruby/method-invocation.json
+++ b/test/corpus/diff-summaries/ruby/method-invocation.json
@@ -55,9 +55,18 @@
"filePaths": [
"method-invocation.rb"
],
- "sha1": "1d64a73244315b920d5fe90966068c5c81009362",
+ "patch": [
+ "diff --git a/method-invocation.rb b/method-invocation.rb",
+ "index e69de29..fbe3bdc 100644",
+ "--- a/method-invocation.rb",
+ "+++ b/method-invocation.rb",
+ "@@ -0,0 +1,3 @@",
+ "+print",
+ "+foo.bar",
+ "+bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "ed107f28c05612907f97f29e8f9ac2d5a37263c2"
+ "shas": "38847e533e9d63b067fd46b4e3bf8e4bcd68f0db..337912159e09103c0f9708052b84b68f93ff3543"
}
,{
"testCaseDescription": "ruby-method-invocation-replacement-insert-test",
@@ -92,7 +101,7 @@
]
}
},
- "summary": "Added the 'foo.bar()' function call"
+ "summary": "Added the 'foo.bar()' method call"
},
{
"span": {
@@ -176,9 +185,25 @@
"filePaths": [
"method-invocation.rb"
],
- "sha1": "ed107f28c05612907f97f29e8f9ac2d5a37263c2",
+ "patch": [
+ "diff --git a/method-invocation.rb b/method-invocation.rb",
+ "index fbe3bdc..c34b65a 100644",
+ "--- a/method-invocation.rb",
+ "+++ b/method-invocation.rb",
+ "@@ -1,3 +1,10 @@",
+ "+print(\"hello world\")",
+ "+foo.bar()",
+ "+bar 2, 3",
+ "+bar(2, 3)",
+ "+print",
+ "+foo.bar",
+ "+bar",
+ " print",
+ " foo.bar",
+ " bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "051f88c30132124c3e49e057d6caf67c99b6fd6c"
+ "shas": "337912159e09103c0f9708052b84b68f93ff3543..ea127bd5909b83d6dee0fb6be0dcc5d7bc4988fd"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-insert-test",
@@ -258,7 +283,7 @@
]
}
},
- "summary": "Deleted the 'foo.bar()' function call"
+ "summary": "Deleted the 'foo.bar()' method call"
},
{
"span": {
@@ -297,9 +322,25 @@
"filePaths": [
"method-invocation.rb"
],
- "sha1": "051f88c30132124c3e49e057d6caf67c99b6fd6c",
+ "patch": [
+ "diff --git a/method-invocation.rb b/method-invocation.rb",
+ "index c34b65a..02ba81a 100644",
+ "--- a/method-invocation.rb",
+ "+++ b/method-invocation.rb",
+ "@@ -1,7 +1,6 @@",
+ "-print(\"hello world\")",
+ "-foo.bar()",
+ "-bar 2, 3",
+ "-bar(2, 3)",
+ "+print",
+ "+foo.bar",
+ "+bar",
+ " print",
+ " foo.bar",
+ " bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "8b83d29df8386a9879d1becf0ec06d64fd1d042c"
+ "shas": "ea127bd5909b83d6dee0fb6be0dcc5d7bc4988fd..d1a8f6f9af6a5bfd0c1668a3d18dc3843c47e114"
}
,{
"testCaseDescription": "ruby-method-invocation-replacement-test",
@@ -334,7 +375,7 @@
]
}
},
- "summary": "Added the 'foo.bar()' function call"
+ "summary": "Added the 'foo.bar()' method call"
},
{
"span": {
@@ -418,9 +459,25 @@
"filePaths": [
"method-invocation.rb"
],
- "sha1": "8b83d29df8386a9879d1becf0ec06d64fd1d042c",
+ "patch": [
+ "diff --git a/method-invocation.rb b/method-invocation.rb",
+ "index 02ba81a..c34b65a 100644",
+ "--- a/method-invocation.rb",
+ "+++ b/method-invocation.rb",
+ "@@ -1,6 +1,7 @@",
+ "-print",
+ "-foo.bar",
+ "-bar",
+ "+print(\"hello world\")",
+ "+foo.bar()",
+ "+bar 2, 3",
+ "+bar(2, 3)",
+ " print",
+ " foo.bar",
+ " bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "3908b684ec871dcc18f2669cdfcdff7c1453e1cb"
+ "shas": "d1a8f6f9af6a5bfd0c1668a3d18dc3843c47e114..5fe58e778dc1c9be8f575f594e744ffefeeb4fc7"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-replacement-test",
@@ -479,9 +536,28 @@
"filePaths": [
"method-invocation.rb"
],
- "sha1": "3908b684ec871dcc18f2669cdfcdff7c1453e1cb",
+ "patch": [
+ "diff --git a/method-invocation.rb b/method-invocation.rb",
+ "index c34b65a..4e17a42 100644",
+ "--- a/method-invocation.rb",
+ "+++ b/method-invocation.rb",
+ "@@ -1,10 +1,7 @@",
+ "+print",
+ "+foo.bar",
+ "+bar",
+ " print(\"hello world\")",
+ " foo.bar()",
+ " bar 2, 3",
+ " bar(2, 3)",
+ "-print",
+ "-foo.bar",
+ "-bar",
+ "-print",
+ "-foo.bar",
+ "-bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "f4d570046d591c1e2a2ac75987a56d34bfbafbdd"
+ "shas": "5fe58e778dc1c9be8f575f594e744ffefeeb4fc7..ec527d127ee949363d1abf4cb103ecfaf766c82a"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-test",
@@ -540,9 +616,21 @@
"filePaths": [
"method-invocation.rb"
],
- "sha1": "f4d570046d591c1e2a2ac75987a56d34bfbafbdd",
+ "patch": [
+ "diff --git a/method-invocation.rb b/method-invocation.rb",
+ "index 4e17a42..2db15c7 100644",
+ "--- a/method-invocation.rb",
+ "+++ b/method-invocation.rb",
+ "@@ -1,6 +1,3 @@",
+ "-print",
+ "-foo.bar",
+ "-bar",
+ " print(\"hello world\")",
+ " foo.bar()",
+ " bar 2, 3"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "62c5df67a438e15a39a77e8c9ad8d3337448d65b"
+ "shas": "ec527d127ee949363d1abf4cb103ecfaf766c82a..f373fd312755ca8a3de02ecce462b619ad8460dc"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-rest-test",
@@ -577,7 +665,7 @@
]
}
},
- "summary": "Deleted the 'foo.bar()' function call"
+ "summary": "Deleted the 'foo.bar()' method call"
},
{
"span": {
@@ -616,7 +704,17 @@
"filePaths": [
"method-invocation.rb"
],
- "sha1": "62c5df67a438e15a39a77e8c9ad8d3337448d65b",
+ "patch": [
+ "diff --git a/method-invocation.rb b/method-invocation.rb",
+ "index 2db15c7..e69de29 100644",
+ "--- a/method-invocation.rb",
+ "+++ b/method-invocation.rb",
+ "@@ -1,4 +0,0 @@",
+ "-print(\"hello world\")",
+ "-foo.bar()",
+ "-bar 2, 3",
+ "-bar(2, 3)"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "9b332f981a2fa42849e4ddc48afca9424480312d"
+ "shas": "f373fd312755ca8a3de02ecce462b619ad8460dc..98200bee05decb871fcfdf6858ee954898880f72"
}]
diff --git a/test/corpus/diff-summaries/ruby/module.json b/test/corpus/diff-summaries/ruby/module.json
index 3bc451940..040022cfb 100644
--- a/test/corpus/diff-summaries/ruby/module.json
+++ b/test/corpus/diff-summaries/ruby/module.json
@@ -11,7 +11,7 @@
1
],
"end": [
- 5,
+ 2,
4
]
}
@@ -25,9 +25,17 @@
"filePaths": [
"module.rb"
],
- "sha1": "1b98fc53dd62922900312603c00866cd0981b695",
+ "patch": [
+ "diff --git a/module.rb b/module.rb",
+ "index e69de29..85026ed 100644",
+ "--- a/module.rb",
+ "+++ b/module.rb",
+ "@@ -0,0 +1,2 @@",
+ "+module Foo",
+ "+end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "6e283321f4bc9eb47f7031ccc075b42aa8c13fd9"
+ "shas": "5df8bfbe172193e6124da27f457fa6fb19547593..9e3d30cbf214e01bac2e8ced270032fc40117c33"
}
,{
"testCaseDescription": "ruby-module-replacement-insert-test",
@@ -42,22 +50,22 @@
1
],
"end": [
- 2,
+ 4,
4
]
}
},
- "summary": "Added the 'Bar::' class"
+ "summary": "Added the 'Foo' module"
},
{
"span": {
"insert": {
"start": [
- 3,
+ 5,
1
],
"end": [
- 7,
+ 6,
4
]
}
@@ -71,44 +79,43 @@
"filePaths": [
"module.rb"
],
- "sha1": "6e283321f4bc9eb47f7031ccc075b42aa8c13fd9",
+ "patch": [
+ "diff --git a/module.rb b/module.rb",
+ "index 85026ed..351dcd2 100644",
+ "--- a/module.rb",
+ "+++ b/module.rb",
+ "@@ -1,2 +1,8 @@",
+ " module Foo",
+ "+ def bar",
+ "+ end",
+ "+end",
+ "+module Foo",
+ "+end",
+ "+module Foo",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "b279f914576a22bad2b5fb0504fd8c198bac02bb"
+ "shas": "9e3d30cbf214e01bac2e8ced270032fc40117c33..070a30dadbd08713621ade900398489f3d5d8d35"
}
,{
"testCaseDescription": "ruby-module-delete-insert-test",
"expectedResult": {
"changes": {
"module.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 5,
- 4
- ]
- }
- },
- "summary": "Added the 'Foo' module"
- },
{
"span": {
"delete": {
"start": [
- 1,
- 1
+ 2,
+ 3
],
"end": [
- 2,
- 4
+ 3,
+ 6
]
}
},
- "summary": "Deleted the 'Bar::' class"
+ "summary": "Deleted the 'bar()' method in the Foo module"
}
]
},
@@ -117,9 +124,21 @@
"filePaths": [
"module.rb"
],
- "sha1": "b279f914576a22bad2b5fb0504fd8c198bac02bb",
+ "patch": [
+ "diff --git a/module.rb b/module.rb",
+ "index 351dcd2..5900129 100644",
+ "--- a/module.rb",
+ "+++ b/module.rb",
+ "@@ -1,6 +1,4 @@",
+ " module Foo",
+ "- def bar",
+ "- end",
+ " end",
+ " module Foo",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "4ab579c0f038b5dd27f2dd0b9596f3563a668b46"
+ "shas": "070a30dadbd08713621ade900398489f3d5d8d35..164b8f9d4149fc6c28f330d764d68e2529ddfe7e"
}
,{
"testCaseDescription": "ruby-module-replacement-test",
@@ -130,31 +149,16 @@
"span": {
"insert": {
"start": [
- 1,
- 1
- ],
- "end": [
2,
- 4
- ]
- }
- },
- "summary": "Added the 'Bar::' class"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 1
+ 3
],
"end": [
- 5,
- 4
+ 3,
+ 6
]
}
},
- "summary": "Deleted the 'Foo' module"
+ "summary": "Added the 'bar()' method in the Foo module"
}
]
},
@@ -163,9 +167,21 @@
"filePaths": [
"module.rb"
],
- "sha1": "4ab579c0f038b5dd27f2dd0b9596f3563a668b46",
+ "patch": [
+ "diff --git a/module.rb b/module.rb",
+ "index 5900129..351dcd2 100644",
+ "--- a/module.rb",
+ "+++ b/module.rb",
+ "@@ -1,4 +1,6 @@",
+ " module Foo",
+ "+ def bar",
+ "+ end",
+ " end",
+ " module Foo",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "4fabcd80f3c94893da6e8580ef502edd2cf991f0"
+ "shas": "164b8f9d4149fc6c28f330d764d68e2529ddfe7e..6790c446e68c1186b5bc0256bcb13ea4f8f98dbc"
}
,{
"testCaseDescription": "ruby-module-delete-replacement-test",
@@ -180,22 +196,22 @@
1
],
"end": [
- 2,
+ 4,
4
]
}
},
- "summary": "Deleted the 'Bar::' class"
+ "summary": "Deleted the 'Foo' module"
},
{
"span": {
"delete": {
"start": [
- 3,
+ 5,
1
],
"end": [
- 7,
+ 6,
4
]
}
@@ -206,16 +222,16 @@
"span": {
"insert": {
"start": [
- 6,
+ 3,
1
],
"end": [
- 7,
+ 6,
4
]
}
},
- "summary": "Added the 'Bar::' class"
+ "summary": "Added the 'Foo' module"
}
]
},
@@ -224,9 +240,25 @@
"filePaths": [
"module.rb"
],
- "sha1": "4fabcd80f3c94893da6e8580ef502edd2cf991f0",
+ "patch": [
+ "diff --git a/module.rb b/module.rb",
+ "index 351dcd2..66871d0 100644",
+ "--- a/module.rb",
+ "+++ b/module.rb",
+ "@@ -1,8 +1,6 @@",
+ " module Foo",
+ "- def bar",
+ "- end",
+ "-end",
+ "-module Foo",
+ " end",
+ " module Foo",
+ "+ def bar",
+ "+ end",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "3249aa5ef88af3ab209b129676a5757e09f9486d"
+ "shas": "6790c446e68c1186b5bc0256bcb13ea4f8f98dbc..ec4ecafdea519cb0020ed5599ff939570d0f854b"
}
,{
"testCaseDescription": "ruby-module-delete-test",
@@ -241,7 +273,7 @@
1
],
"end": [
- 5,
+ 2,
4
]
}
@@ -255,9 +287,21 @@
"filePaths": [
"module.rb"
],
- "sha1": "3249aa5ef88af3ab209b129676a5757e09f9486d",
+ "patch": [
+ "diff --git a/module.rb b/module.rb",
+ "index 66871d0..56f77bb 100644",
+ "--- a/module.rb",
+ "+++ b/module.rb",
+ "@@ -1,6 +1,4 @@",
+ " module Foo",
+ "-end",
+ "-module Foo",
+ " def bar",
+ " end",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e1ba7de1fff93d9da58e7f7bce31c4634de63d79"
+ "shas": "ec4ecafdea519cb0020ed5599ff939570d0f854b..57a8fb4e465c80ab42466968a539a77bf8880f5a"
}
,{
"testCaseDescription": "ruby-module-delete-rest-test",
@@ -272,12 +316,12 @@
1
],
"end": [
- 2,
+ 4,
4
]
}
},
- "summary": "Deleted the 'Bar::' class"
+ "summary": "Deleted the 'Foo' module"
}
]
},
@@ -286,7 +330,17 @@
"filePaths": [
"module.rb"
],
- "sha1": "e1ba7de1fff93d9da58e7f7bce31c4634de63d79",
+ "patch": [
+ "diff --git a/module.rb b/module.rb",
+ "index 56f77bb..e69de29 100644",
+ "--- a/module.rb",
+ "+++ b/module.rb",
+ "@@ -1,4 +0,0 @@",
+ "-module Foo",
+ "- def bar",
+ "- end",
+ "-end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "932ab2e771298de02435e6560b092f44116db759"
+ "shas": "57a8fb4e465c80ab42466968a539a77bf8880f5a..1713f7f3e2aa6a1e643842fde9382ce098c08363"
}]
diff --git a/test/corpus/diff-summaries/ruby/multiple-assignments.json b/test/corpus/diff-summaries/ruby/multiple-assignments.json
index 4e075d4b7..180a9ebe0 100644
--- a/test/corpus/diff-summaries/ruby/multiple-assignments.json
+++ b/test/corpus/diff-summaries/ruby/multiple-assignments.json
@@ -10,24 +10,49 @@
1,
1
],
+ "end": [
+ 1,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'x' identifier"
+ }
+ ]
+ },
+ "errors": {
+ "multiple-assignments.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 2
+ ],
"end": [
1,
21
]
}
},
- "summary": "Added the 'x(…, y, z, 20, 30)' function call"
+ "summary": "Added the ', y, z = 10, 20, 30' at line 1, column 2 - line 1, column 21"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"multiple-assignments.rb"
],
- "sha1": "65cdd278c64ea23aacd3c8cf11e6f52864fa66ff",
+ "patch": [
+ "diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
+ "index e69de29..d5c6132 100644",
+ "--- a/multiple-assignments.rb",
+ "+++ b/multiple-assignments.rb",
+ "@@ -0,0 +1 @@",
+ "+x, y, z = 10, 20, 30"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "9f2f6fc575ac8807150427ba4da1f8de11e74648"
+ "shas": "f99339c141252271935202cb6c4b96a5076cf574..98a5ec1c60abaf1b78a8b0e337b95a0f962b25ac"
}
,{
"testCaseDescription": "ruby-multiple-assignments-replacement-insert-test",
@@ -43,11 +68,11 @@
],
"end": [
1,
- 21
+ 2
]
}
},
- "summary": "Added the 'x(…, 40)' function call"
+ "summary": "Added the 'x' identifier"
},
{
"span": {
@@ -58,43 +83,70 @@
],
"end": [
2,
- 21
+ 2
]
}
},
- "summary": "Added the 'x(…, y, z, 20, 30)' function call"
+ "summary": "Added the 'x' identifier"
}
]
},
- "errors": {}
- },
- "filePaths": [
- "multiple-assignments.rb"
- ],
- "sha1": "9f2f6fc575ac8807150427ba4da1f8de11e74648",
- "gitDir": "test/corpus/repos/ruby",
- "sha2": "e6d87164c6073959e327ce3e3552bb0215c65d18"
-}
-,{
- "testCaseDescription": "ruby-multiple-assignments-delete-insert-test",
- "expectedResult": {
- "changes": {
+ "errors": {
"multiple-assignments.rb": [
{
"span": {
"insert": {
"start": [
1,
- 4
+ 2
],
"end": [
1,
- 5
+ 21
]
}
},
- "summary": "Added the 'y' identifier in the x(…, y, z, 20, 30) function call"
+ "summary": "Added the ', y = aVariable, 40' at line 1, column 2 - line 1, column 21"
},
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 2
+ ],
+ "end": [
+ 2,
+ 21
+ ]
+ }
+ },
+ "summary": "Added the ', y, z = 10, 20, 30' at line 2, column 2 - line 2, column 21"
+ }
+ ]
+ }
+ },
+ "filePaths": [
+ "multiple-assignments.rb"
+ ],
+ "patch": [
+ "diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
+ "index d5c6132..ffc26fa 100644",
+ "--- a/multiple-assignments.rb",
+ "+++ b/multiple-assignments.rb",
+ "@@ -1 +1,3 @@",
+ "+x, y = aVariable, 40",
+ "+x, y, z = 10, 20, 30",
+ " x, y, z = 10, 20, 30"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "98a5ec1c60abaf1b78a8b0e337b95a0f962b25ac..c48c21b17b29aa5e6bd49b027c9b43a9e8de8555"
+}
+,{
+ "testCaseDescription": "ruby-multiple-assignments-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "multiple-assignments.rb": [
{
"span": {
"replace": [
@@ -103,48 +155,6 @@
1,
2
],
- "end": [
- 1,
- 17
- ]
- },
- {
- "start": [
- 1,
- 7
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
- },
- "summary": "Replaced the ', y = aVariable' at line 1, column 2 - line 1, column 17 with the 'z' assignment in the x(…, y, z, 20, 30) function call"
- },
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 15
- ],
- "end": [
- 1,
- 17
- ]
- }
- },
- "summary": "Added '20' in the x(…, y, z, 20, 30) function call"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 19
- ],
"end": [
1,
21
@@ -153,7 +163,7 @@
{
"start": [
1,
- 19
+ 2
],
"end": [
1,
@@ -162,36 +172,28 @@
}
]
},
- "summary": "Replaced '40' with '30' in the x(…, y, z, 20, 30) function call"
+ "summary": "Replaced the ', y = aVariable, 40' at line 1, column 2 - line 1, column 21 with the ', y, z = 10, 20, 30' at line 1, column 2 - line 1, column 21"
}
]
},
- "errors": {
- "multiple-assignments.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 2
- ],
- "end": [
- 1,
- 3
- ]
- }
- },
- "summary": "Added the ',' at line 1, column 2 - line 1, column 3 in the x(…, y, z, 20, 30) function call"
- }
- ]
- }
+ "errors": {}
},
"filePaths": [
"multiple-assignments.rb"
],
- "sha1": "e6d87164c6073959e327ce3e3552bb0215c65d18",
+ "patch": [
+ "diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
+ "index ffc26fa..7a83199 100644",
+ "--- a/multiple-assignments.rb",
+ "+++ b/multiple-assignments.rb",
+ "@@ -1,3 +1,3 @@",
+ "-x, y = aVariable, 40",
+ "+x, y, z = 10, 20, 30",
+ " x, y, z = 10, 20, 30",
+ " x, y, z = 10, 20, 30"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "75c863e1f261a3fbb80129fd923b041ddf5d36f4"
+ "shas": "c48c21b17b29aa5e6bd49b027c9b43a9e8de8555..980e039b8ec804ddd8dbddc853077d19dbf9120a"
}
,{
"testCaseDescription": "ruby-multiple-assignments-replacement-test",
@@ -200,122 +202,51 @@
"multiple-assignments.rb": [
{
"span": {
- "insert": {
- "start": [
- 1,
- 19
- ],
- "end": [
- 1,
- 21
- ]
- }
+ "replace": [
+ {
+ "start": [
+ 1,
+ 2
+ ],
+ "end": [
+ 1,
+ 21
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 2
+ ],
+ "end": [
+ 1,
+ 21
+ ]
+ }
+ ]
},
- "summary": "Added '40' in the x(…, 40) function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 4
- ],
- "end": [
- 1,
- 5
- ]
- }
- },
- "summary": "Deleted the 'y' identifier in the x(…, 40) function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 7
- ],
- "end": [
- 1,
- 13
- ]
- }
- },
- "summary": "Deleted the 'z' assignment in the x(…, 40) function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 15
- ],
- "end": [
- 1,
- 17
- ]
- }
- },
- "summary": "Deleted '20' in the x(…, 40) function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 19
- ],
- "end": [
- 1,
- 21
- ]
- }
- },
- "summary": "Deleted '30' in the x(…, 40) function call"
+ "summary": "Replaced the ', y, z = 10, 20, 30' at line 1, column 2 - line 1, column 21 with the ', y = aVariable, 40' at line 1, column 2 - line 1, column 21"
}
]
},
- "errors": {
- "multiple-assignments.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 2
- ],
- "end": [
- 1,
- 17
- ]
- }
- },
- "summary": "Added the ', y = aVariable' at line 1, column 2 - line 1, column 17 in the x(…, 40) function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 2
- ],
- "end": [
- 1,
- 3
- ]
- }
- },
- "summary": "Deleted the ',' at line 1, column 2 - line 1, column 3 in the x(…, 40) function call"
- }
- ]
- }
+ "errors": {}
},
"filePaths": [
"multiple-assignments.rb"
],
- "sha1": "75c863e1f261a3fbb80129fd923b041ddf5d36f4",
+ "patch": [
+ "diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
+ "index 7a83199..ffc26fa 100644",
+ "--- a/multiple-assignments.rb",
+ "+++ b/multiple-assignments.rb",
+ "@@ -1,3 +1,3 @@",
+ "-x, y, z = 10, 20, 30",
+ "+x, y = aVariable, 40",
+ " x, y, z = 10, 20, 30",
+ " x, y, z = 10, 20, 30"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "1b8b525816da68c9b71590d195910c907ec07491"
+ "shas": "980e039b8ec804ddd8dbddc853077d19dbf9120a..859efa4bd7103d88fddb33e725029b020f6194ac"
}
,{
"testCaseDescription": "ruby-multiple-assignments-delete-replacement-test",
@@ -331,52 +262,77 @@
],
"end": [
1,
- 21
+ 2
]
}
},
- "summary": "Deleted the 'x(…, 40)' function call"
+ "summary": "Deleted the 'x' identifier"
},
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 3,
+ 2
+ ],
+ "end": [
+ 3,
+ 21
+ ]
+ },
+ {
+ "start": [
+ 2,
+ 2
+ ],
+ "end": [
+ 2,
+ 21
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the ', y, z = 10, 20, 30' at line 3, column 2 - line 3, column 21 with the ', y = aVariable, 40' at line 2, column 2 - line 2, column 21"
+ }
+ ]
+ },
+ "errors": {
+ "multiple-assignments.rb": [
{
"span": {
"delete": {
"start": [
- 2,
- 1
+ 1,
+ 2
],
"end": [
- 2,
+ 1,
21
]
}
},
- "summary": "Deleted the 'x(…, y, z, 20, 30)' function call"
- },
- {
- "span": {
- "insert": {
- "start": [
- 2,
- 1
- ],
- "end": [
- 2,
- 21
- ]
- }
- },
- "summary": "Added the 'x(…, 40)' function call"
+ "summary": "Deleted the ', y = aVariable, 40' at line 1, column 2 - line 1, column 21"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"multiple-assignments.rb"
],
- "sha1": "1b8b525816da68c9b71590d195910c907ec07491",
+ "patch": [
+ "diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
+ "index ffc26fa..64eb96e 100644",
+ "--- a/multiple-assignments.rb",
+ "+++ b/multiple-assignments.rb",
+ "@@ -1,3 +1,2 @@",
+ "-x, y = aVariable, 40",
+ "-x, y, z = 10, 20, 30",
+ " x, y, z = 10, 20, 30",
+ "+x, y = aVariable, 40"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "7b56b3f5cc93525db8296697cf4172342acf9808"
+ "shas": "859efa4bd7103d88fddb33e725029b020f6194ac..0db7d6e491af2074c50a647bd3fde1732a13e8a1"
}
,{
"testCaseDescription": "ruby-multiple-assignments-delete-test",
@@ -390,24 +346,50 @@
1,
1
],
+ "end": [
+ 1,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'x' identifier"
+ }
+ ]
+ },
+ "errors": {
+ "multiple-assignments.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 2
+ ],
"end": [
1,
21
]
}
},
- "summary": "Deleted the 'x(…, y, z, 20, 30)' function call"
+ "summary": "Deleted the ', y, z = 10, 20, 30' at line 1, column 2 - line 1, column 21"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"multiple-assignments.rb"
],
- "sha1": "7b56b3f5cc93525db8296697cf4172342acf9808",
+ "patch": [
+ "diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
+ "index 64eb96e..9ddb504 100644",
+ "--- a/multiple-assignments.rb",
+ "+++ b/multiple-assignments.rb",
+ "@@ -1,2 +1 @@",
+ "-x, y, z = 10, 20, 30",
+ " x, y = aVariable, 40"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "87e60bd80ad17dec9827433189e28c6b26e84d90"
+ "shas": "0db7d6e491af2074c50a647bd3fde1732a13e8a1..c6eec07b5b8f35169a6c9fec9bf0ec78776a1dc7"
}
,{
"testCaseDescription": "ruby-multiple-assignments-delete-rest-test",
@@ -421,22 +403,47 @@
1,
1
],
+ "end": [
+ 1,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'x' identifier"
+ }
+ ]
+ },
+ "errors": {
+ "multiple-assignments.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 2
+ ],
"end": [
1,
21
]
}
},
- "summary": "Deleted the 'x(…, 40)' function call"
+ "summary": "Deleted the ', y = aVariable, 40' at line 1, column 2 - line 1, column 21"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"multiple-assignments.rb"
],
- "sha1": "87e60bd80ad17dec9827433189e28c6b26e84d90",
+ "patch": [
+ "diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
+ "index 9ddb504..e69de29 100644",
+ "--- a/multiple-assignments.rb",
+ "+++ b/multiple-assignments.rb",
+ "@@ -1 +0,0 @@",
+ "-x, y = aVariable, 40"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "99cb54a96833cce9f6add73f966884f7b735594e"
+ "shas": "c6eec07b5b8f35169a6c9fec9bf0ec78776a1dc7..118c643eafd1e37132a89af409f899e58621d0e4"
}]
diff --git a/test/corpus/diff-summaries/ruby/number.json b/test/corpus/diff-summaries/ruby/number.json
index 76e27ec33..f0d3fbf81 100644
--- a/test/corpus/diff-summaries/ruby/number.json
+++ b/test/corpus/diff-summaries/ruby/number.json
@@ -115,9 +115,23 @@
"filePaths": [
"number.rb"
],
- "sha1": "0957bae761de5bf738359a6690f06c633b38a43d",
+ "patch": [
+ "diff --git a/number.rb b/number.rb",
+ "index e69de29..1a73a0e 100644",
+ "--- a/number.rb",
+ "+++ b/number.rb",
+ "@@ -0,0 +1,8 @@",
+ "+1234",
+ "+1_234",
+ "+0d1_234",
+ "+0xa_bcd_ef0_123_456_789",
+ "+0o1234567",
+ "+0b1_0",
+ "+1.234_5e678_90",
+ "+"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "aeda46e163198f22c8eaeda07966064567ffe4cc"
+ "shas": "0f08e943de503b5d714186206425966f0517ddec..c2c6dd7da94b8e4a0cd8b0acdd5e8526f05355f2"
}
,{
"testCaseDescription": "ruby-number-replacement-insert-test",
@@ -368,9 +382,34 @@
"filePaths": [
"number.rb"
],
- "sha1": "aeda46e163198f22c8eaeda07966064567ffe4cc",
+ "patch": [
+ "diff --git a/number.rb b/number.rb",
+ "index 1a73a0e..ed36c77 100644",
+ "--- a/number.rb",
+ "+++ b/number.rb",
+ "@@ -1,3 +1,19 @@",
+ "+1235",
+ "+1_235",
+ "+0d1_235",
+ "+0xa_bcd_ef0_123_456_788",
+ "+0o1234576",
+ "+0b1_1",
+ "+1.234_5e678_91",
+ "+",
+ "+1234",
+ "+1_234",
+ "+0d1_234",
+ "+0xa_bcd_ef0_123_456_789",
+ "+0o1234567",
+ "+0b1_0",
+ "+1.234_5e678_90",
+ "+",
+ " 1234",
+ " 1_234",
+ " 0d1_234"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "33f99dbd2d8065e4b180835837107a5e289d1928"
+ "shas": "c2c6dd7da94b8e4a0cd8b0acdd5e8526f05355f2..d243b819564a35405d46f58255eb9d46bc9b2e99"
}
,{
"testCaseDescription": "ruby-number-delete-insert-test",
@@ -594,9 +633,32 @@
"filePaths": [
"number.rb"
],
- "sha1": "33f99dbd2d8065e4b180835837107a5e289d1928",
+ "patch": [
+ "diff --git a/number.rb b/number.rb",
+ "index ed36c77..ad686c2 100644",
+ "--- a/number.rb",
+ "+++ b/number.rb",
+ "@@ -1,10 +1,10 @@",
+ "-1235",
+ "-1_235",
+ "-0d1_235",
+ "-0xa_bcd_ef0_123_456_788",
+ "-0o1234576",
+ "-0b1_1",
+ "-1.234_5e678_91",
+ "+1234",
+ "+1_234",
+ "+0d1_234",
+ "+0xa_bcd_ef0_123_456_789",
+ "+0o1234567",
+ "+0b1_0",
+ "+1.234_5e678_90",
+ " ",
+ " 1234",
+ " 1_234"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "fef6e24bc278c784f035efa55f2c71c41f409b81"
+ "shas": "d243b819564a35405d46f58255eb9d46bc9b2e99..62be4a00fb4fc32b3296ff1c8ffc0bb01b15379a"
}
,{
"testCaseDescription": "ruby-number-replacement-test",
@@ -820,9 +882,32 @@
"filePaths": [
"number.rb"
],
- "sha1": "fef6e24bc278c784f035efa55f2c71c41f409b81",
+ "patch": [
+ "diff --git a/number.rb b/number.rb",
+ "index ad686c2..ed36c77 100644",
+ "--- a/number.rb",
+ "+++ b/number.rb",
+ "@@ -1,10 +1,10 @@",
+ "-1234",
+ "-1_234",
+ "-0d1_234",
+ "-0xa_bcd_ef0_123_456_789",
+ "-0o1234567",
+ "-0b1_0",
+ "-1.234_5e678_90",
+ "+1235",
+ "+1_235",
+ "+0d1_235",
+ "+0xa_bcd_ef0_123_456_788",
+ "+0o1234576",
+ "+0b1_1",
+ "+1.234_5e678_91",
+ " ",
+ " 1234",
+ " 1_234"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "03b758f4230c3e65e2bfc2f42dbb8f263c8c3623"
+ "shas": "62be4a00fb4fc32b3296ff1c8ffc0bb01b15379a..bc3466b947814264cb346aa410b9210d315be80b"
}
,{
"testCaseDescription": "ruby-number-delete-replacement-test",
@@ -1181,9 +1266,45 @@
"filePaths": [
"number.rb"
],
- "sha1": "03b758f4230c3e65e2bfc2f42dbb8f263c8c3623",
+ "patch": [
+ "diff --git a/number.rb b/number.rb",
+ "index ed36c77..033221c 100644",
+ "--- a/number.rb",
+ "+++ b/number.rb",
+ "@@ -1,11 +1,3 @@",
+ "-1235",
+ "-1_235",
+ "-0d1_235",
+ "-0xa_bcd_ef0_123_456_788",
+ "-0o1234576",
+ "-0b1_1",
+ "-1.234_5e678_91",
+ "-",
+ " 1234",
+ " 1_234",
+ " 0d1_234",
+ "@@ -14,11 +6,11 @@",
+ " 0b1_0",
+ " 1.234_5e678_90",
+ " ",
+ "-1234",
+ "-1_234",
+ "-0d1_234",
+ "-0xa_bcd_ef0_123_456_789",
+ "-0o1234567",
+ "-0b1_0",
+ "-1.234_5e678_90",
+ "+1235",
+ "+1_235",
+ "+0d1_235",
+ "+0xa_bcd_ef0_123_456_788",
+ "+0o1234576",
+ "+0b1_1",
+ "+1.234_5e678_91",
+ " "
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e005d4540a533e8fcd0226d43ac774df7f9b478e"
+ "shas": "bc3466b947814264cb346aa410b9210d315be80b..e0cf7e6edc8c07a9a62b40e4d3baee6de8b7223c"
}
,{
"testCaseDescription": "ruby-number-delete-test",
@@ -1332,9 +1453,26 @@
"filePaths": [
"number.rb"
],
- "sha1": "e005d4540a533e8fcd0226d43ac774df7f9b478e",
+ "patch": [
+ "diff --git a/number.rb b/number.rb",
+ "index 033221c..344510e 100644",
+ "--- a/number.rb",
+ "+++ b/number.rb",
+ "@@ -1,11 +1,3 @@",
+ "-1234",
+ "-1_234",
+ "-0d1_234",
+ "-0xa_bcd_ef0_123_456_789",
+ "-0o1234567",
+ "-0b1_0",
+ "-1.234_5e678_90",
+ "-",
+ " 1235",
+ " 1_235",
+ " 0d1_235"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "d7654d564470fc8f926394c4410de1388e2d9e20"
+ "shas": "e0cf7e6edc8c07a9a62b40e4d3baee6de8b7223c..43f4b885483cf6653fbc4344244d4908a9509e02"
}
,{
"testCaseDescription": "ruby-number-delete-rest-test",
@@ -1453,7 +1591,21 @@
"filePaths": [
"number.rb"
],
- "sha1": "d7654d564470fc8f926394c4410de1388e2d9e20",
+ "patch": [
+ "diff --git a/number.rb b/number.rb",
+ "index 344510e..e69de29 100644",
+ "--- a/number.rb",
+ "+++ b/number.rb",
+ "@@ -1,8 +0,0 @@",
+ "-1235",
+ "-1_235",
+ "-0d1_235",
+ "-0xa_bcd_ef0_123_456_788",
+ "-0o1234576",
+ "-0b1_1",
+ "-1.234_5e678_91",
+ "-"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "cf75d6b80230785d209c010331669dcc53f3131c"
+ "shas": "43f4b885483cf6653fbc4344244d4908a9509e02..54b8896e3161e23f3cc38414d860e49c385d98ea"
}]
diff --git a/test/corpus/diff-summaries/ruby/percent-array.json b/test/corpus/diff-summaries/ruby/percent-array.json
index 4d2095002..0dd4b128b 100644
--- a/test/corpus/diff-summaries/ruby/percent-array.json
+++ b/test/corpus/diff-summaries/ruby/percent-array.json
@@ -25,9 +25,16 @@
"filePaths": [
"percent-array.rb"
],
- "sha1": "fb977a1a932fedffdf11b59b7039edfee929898b",
+ "patch": [
+ "diff --git a/percent-array.rb b/percent-array.rb",
+ "index e69de29..f2bc7a3 100644",
+ "--- a/percent-array.rb",
+ "+++ b/percent-array.rb",
+ "@@ -0,0 +1 @@",
+ "+%w(one two)"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "59826bd1c0ef17b0d316b84e12d407343567b51e"
+ "shas": "79b196cace027a076f4ba235171fd4f409bdaba9..60bbbb2dee1ceb124b3a5732a1f3ee63ec515497"
}
,{
"testCaseDescription": "ruby-percent-array-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"percent-array.rb"
],
- "sha1": "59826bd1c0ef17b0d316b84e12d407343567b51e",
+ "patch": [
+ "diff --git a/percent-array.rb b/percent-array.rb",
+ "index f2bc7a3..a706392 100644",
+ "--- a/percent-array.rb",
+ "+++ b/percent-array.rb",
+ "@@ -1 +1,3 @@",
+ "+%W(one #{b} three)",
+ "+%w(one two)",
+ " %w(one two)"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "8c3310689a60ae2aeab52560665f69a75d0e6a80"
+ "shas": "60bbbb2dee1ceb124b3a5732a1f3ee63ec515497..7331cd0d8952471a92cddf2c85b3a8a3ce74846d"
}
,{
"testCaseDescription": "ruby-percent-array-delete-insert-test",
@@ -102,9 +118,19 @@
"filePaths": [
"percent-array.rb"
],
- "sha1": "8c3310689a60ae2aeab52560665f69a75d0e6a80",
+ "patch": [
+ "diff --git a/percent-array.rb b/percent-array.rb",
+ "index a706392..339b21e 100644",
+ "--- a/percent-array.rb",
+ "+++ b/percent-array.rb",
+ "@@ -1,3 +1,3 @@",
+ "-%W(one #{b} three)",
+ "+%w(one two)",
+ " %w(one two)",
+ " %w(one two)"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "a9f6587196cdbbe93040f98b10dd42e56a61606b"
+ "shas": "7331cd0d8952471a92cddf2c85b3a8a3ce74846d..0a03996c67d51dc60959a36d35bb2bb781eff19b"
}
,{
"testCaseDescription": "ruby-percent-array-replacement-test",
@@ -133,9 +159,19 @@
"filePaths": [
"percent-array.rb"
],
- "sha1": "a9f6587196cdbbe93040f98b10dd42e56a61606b",
+ "patch": [
+ "diff --git a/percent-array.rb b/percent-array.rb",
+ "index 339b21e..a706392 100644",
+ "--- a/percent-array.rb",
+ "+++ b/percent-array.rb",
+ "@@ -1,3 +1,3 @@",
+ "-%w(one two)",
+ "+%W(one #{b} three)",
+ " %w(one two)",
+ " %w(one two)"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e036c90a9157248f492faab6f647dc8328a81bb7"
+ "shas": "0a03996c67d51dc60959a36d35bb2bb781eff19b..864617da3f66a3b16b6ab2c7c63a0a449669fc01"
}
,{
"testCaseDescription": "ruby-percent-array-delete-replacement-test",
@@ -194,9 +230,19 @@
"filePaths": [
"percent-array.rb"
],
- "sha1": "e036c90a9157248f492faab6f647dc8328a81bb7",
+ "patch": [
+ "diff --git a/percent-array.rb b/percent-array.rb",
+ "index a706392..1e3e29b 100644",
+ "--- a/percent-array.rb",
+ "+++ b/percent-array.rb",
+ "@@ -1,3 +1,2 @@",
+ "-%W(one #{b} three)",
+ "-%w(one two)",
+ " %w(one two)",
+ "+%W(one #{b} three)"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "ed775facea4cfb87fbd958eba63c3d0b731ae89f"
+ "shas": "864617da3f66a3b16b6ab2c7c63a0a449669fc01..0bee45a0f42e71f1162b4150b0647cf13a05b8f8"
}
,{
"testCaseDescription": "ruby-percent-array-delete-test",
@@ -225,9 +271,17 @@
"filePaths": [
"percent-array.rb"
],
- "sha1": "ed775facea4cfb87fbd958eba63c3d0b731ae89f",
+ "patch": [
+ "diff --git a/percent-array.rb b/percent-array.rb",
+ "index 1e3e29b..54153c4 100644",
+ "--- a/percent-array.rb",
+ "+++ b/percent-array.rb",
+ "@@ -1,2 +1 @@",
+ "-%w(one two)",
+ " %W(one #{b} three)"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "45e409958bde72eed0dbf21ebde75141f9cc0ca7"
+ "shas": "0bee45a0f42e71f1162b4150b0647cf13a05b8f8..4a8ac79d914f73b9e92da2948689badc6676ca31"
}
,{
"testCaseDescription": "ruby-percent-array-delete-rest-test",
@@ -256,7 +310,14 @@
"filePaths": [
"percent-array.rb"
],
- "sha1": "45e409958bde72eed0dbf21ebde75141f9cc0ca7",
+ "patch": [
+ "diff --git a/percent-array.rb b/percent-array.rb",
+ "index 54153c4..e69de29 100644",
+ "--- a/percent-array.rb",
+ "+++ b/percent-array.rb",
+ "@@ -1 +0,0 @@",
+ "-%W(one #{b} three)"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "bf01ed653791dfe5beb43e85c33f6e2d069fefc2"
+ "shas": "4a8ac79d914f73b9e92da2948689badc6676ca31..39e3abbd0e3332afc2314759fdd350cba39b8e28"
}]
diff --git a/test/corpus/diff-summaries/ruby/pseudo-variables.json b/test/corpus/diff-summaries/ruby/pseudo-variables.json
index c1bc2ac21..039711949 100644
--- a/test/corpus/diff-summaries/ruby/pseudo-variables.json
+++ b/test/corpus/diff-summaries/ruby/pseudo-variables.json
@@ -55,9 +55,19 @@
"filePaths": [
"pseudo-variables.rb"
],
- "sha1": "ce3778a99ea788f6ff75371e985c61c1a240cf13",
+ "patch": [
+ "diff --git a/pseudo-variables.rb b/pseudo-variables.rb",
+ "index e69de29..2be92bc 100644",
+ "--- a/pseudo-variables.rb",
+ "+++ b/pseudo-variables.rb",
+ "@@ -0,0 +1,4 @@",
+ "+nil",
+ "+self",
+ "+false",
+ "+true"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "733f12cf3bffe56c4c06348db5254dc45f24c4ac"
+ "shas": "052401261edd2497b65b3546c0220694e89a03fb..eb4638e54cfb32940ad29a5070b90e44213e351b"
}
,{
"testCaseDescription": "ruby-pseudo-variables-replacement-insert-test",
@@ -161,9 +171,26 @@
"filePaths": [
"pseudo-variables.rb"
],
- "sha1": "733f12cf3bffe56c4c06348db5254dc45f24c4ac",
+ "patch": [
+ "diff --git a/pseudo-variables.rb b/pseudo-variables.rb",
+ "index 2be92bc..e5837f2 100644",
+ "--- a/pseudo-variables.rb",
+ "+++ b/pseudo-variables.rb",
+ "@@ -1,3 +1,11 @@",
+ "+self",
+ "+NIL",
+ "+TRUE",
+ "+FALSE",
+ "+nil",
+ "+self",
+ "+false",
+ "+true",
+ " nil",
+ " self",
+ " false"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "a05d3f95aec10f667adf4b0c4e1cdd8bd606e377"
+ "shas": "eb4638e54cfb32940ad29a5070b90e44213e351b..35f40623910a2294db51fb259e7b4af6954dcb0f"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-insert-test",
@@ -261,9 +288,25 @@
"filePaths": [
"pseudo-variables.rb"
],
- "sha1": "a05d3f95aec10f667adf4b0c4e1cdd8bd606e377",
+ "patch": [
+ "diff --git a/pseudo-variables.rb b/pseudo-variables.rb",
+ "index e5837f2..e3f5814 100644",
+ "--- a/pseudo-variables.rb",
+ "+++ b/pseudo-variables.rb",
+ "@@ -1,7 +1,7 @@",
+ "+nil",
+ " self",
+ "-NIL",
+ "-TRUE",
+ "-FALSE",
+ "+false",
+ "+true",
+ " nil",
+ " self",
+ " false"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "18b9418c8995dcee39f6daae644bc82170913dda"
+ "shas": "35f40623910a2294db51fb259e7b4af6954dcb0f..7228ef9145f92f76d1ce1f9af3111a0a9f402636"
}
,{
"testCaseDescription": "ruby-pseudo-variables-replacement-test",
@@ -361,9 +404,25 @@
"filePaths": [
"pseudo-variables.rb"
],
- "sha1": "18b9418c8995dcee39f6daae644bc82170913dda",
+ "patch": [
+ "diff --git a/pseudo-variables.rb b/pseudo-variables.rb",
+ "index e3f5814..e5837f2 100644",
+ "--- a/pseudo-variables.rb",
+ "+++ b/pseudo-variables.rb",
+ "@@ -1,7 +1,7 @@",
+ "-nil",
+ " self",
+ "-false",
+ "-true",
+ "+NIL",
+ "+TRUE",
+ "+FALSE",
+ " nil",
+ " self",
+ " false"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "21335e57824052719d0a357137bc271a3806012b"
+ "shas": "7228ef9145f92f76d1ce1f9af3111a0a9f402636..247085a3bb210f1ee85ba391c96725e7311fce20"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-replacement-test",
@@ -512,9 +571,30 @@
"filePaths": [
"pseudo-variables.rb"
],
- "sha1": "21335e57824052719d0a357137bc271a3806012b",
+ "patch": [
+ "diff --git a/pseudo-variables.rb b/pseudo-variables.rb",
+ "index e5837f2..8873ea5 100644",
+ "--- a/pseudo-variables.rb",
+ "+++ b/pseudo-variables.rb",
+ "@@ -1,12 +1,8 @@",
+ "-self",
+ "-NIL",
+ "-TRUE",
+ "-FALSE",
+ " nil",
+ " self",
+ " false",
+ " true",
+ "-nil",
+ " self",
+ "-false",
+ "-true",
+ "+NIL",
+ "+TRUE",
+ "+FALSE"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "657002ff458fa50b32477904d9b48ef106b3a45e"
+ "shas": "247085a3bb210f1ee85ba391c96725e7311fce20..3c4b678a23d925ae1efdd94cb47b240c63af6ff1"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-test",
@@ -573,9 +653,22 @@
"filePaths": [
"pseudo-variables.rb"
],
- "sha1": "657002ff458fa50b32477904d9b48ef106b3a45e",
+ "patch": [
+ "diff --git a/pseudo-variables.rb b/pseudo-variables.rb",
+ "index 8873ea5..30bb4d2 100644",
+ "--- a/pseudo-variables.rb",
+ "+++ b/pseudo-variables.rb",
+ "@@ -1,7 +1,3 @@",
+ "-nil",
+ "-self",
+ "-false",
+ "-true",
+ " self",
+ " NIL",
+ " TRUE"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "91d164b57939d4fcff85c1889c113feb71f90f13"
+ "shas": "3c4b678a23d925ae1efdd94cb47b240c63af6ff1..349da6fa88ae41a84f50976e21182a5d9cd7a701"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-rest-test",
@@ -634,7 +727,17 @@
"filePaths": [
"pseudo-variables.rb"
],
- "sha1": "91d164b57939d4fcff85c1889c113feb71f90f13",
+ "patch": [
+ "diff --git a/pseudo-variables.rb b/pseudo-variables.rb",
+ "index 30bb4d2..e69de29 100644",
+ "--- a/pseudo-variables.rb",
+ "+++ b/pseudo-variables.rb",
+ "@@ -1,4 +0,0 @@",
+ "-self",
+ "-NIL",
+ "-TRUE",
+ "-FALSE"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "4cf0b1c84b725b7ecea2d0e2524d4aa83e9aa9f0"
+ "shas": "349da6fa88ae41a84f50976e21182a5d9cd7a701..f8cc3489b25f8d1857452648c25c51084dbdbdb9"
}]
diff --git a/test/corpus/diff-summaries/ruby/regex.json b/test/corpus/diff-summaries/ruby/regex.json
index 8f4cb14a8..b55291eca 100644
--- a/test/corpus/diff-summaries/ruby/regex.json
+++ b/test/corpus/diff-summaries/ruby/regex.json
@@ -25,9 +25,16 @@
"filePaths": [
"regex.rb"
],
- "sha1": "e9bfaab31e3a83e3c8e8d890bd8e2a6cf1f5a529",
+ "patch": [
+ "diff --git a/regex.rb b/regex.rb",
+ "index e69de29..02dce9d 100644",
+ "--- a/regex.rb",
+ "+++ b/regex.rb",
+ "@@ -0,0 +1 @@",
+ "+/^(foo|bar[^_])$/i"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "c55fee07c0dce3d63289fc564118d10dd309a613"
+ "shas": "956b136e24f76c977fefd27d5368ecd527f721ec..49cb17b4244d627bd084dab1c7248c48a3cdb7cc"
}
,{
"testCaseDescription": "ruby-regex-replacement-insert-test",
@@ -86,9 +93,19 @@
"filePaths": [
"regex.rb"
],
- "sha1": "c55fee07c0dce3d63289fc564118d10dd309a613",
+ "patch": [
+ "diff --git a/regex.rb b/regex.rb",
+ "index 02dce9d..c801d61 100644",
+ "--- a/regex.rb",
+ "+++ b/regex.rb",
+ "@@ -1 +1,4 @@",
+ "+%r/a/",
+ "+%rc>",
+ "+/^(foo|bar[^_])$/i",
+ " /^(foo|bar[^_])$/i"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e0db422ba580f8ebd34a40bbda085bad23c31805"
+ "shas": "49cb17b4244d627bd084dab1c7248c48a3cdb7cc..a73a7605d28b1fe2b09ce87d8db7426ea6295610"
}
,{
"testCaseDescription": "ruby-regex-delete-insert-test",
@@ -144,9 +161,20 @@
"filePaths": [
"regex.rb"
],
- "sha1": "e0db422ba580f8ebd34a40bbda085bad23c31805",
+ "patch": [
+ "diff --git a/regex.rb b/regex.rb",
+ "index c801d61..42d4984 100644",
+ "--- a/regex.rb",
+ "+++ b/regex.rb",
+ "@@ -1,4 +1,3 @@",
+ "-%r/a/",
+ "-%rc>",
+ "+/^(foo|bar[^_])$/i",
+ " /^(foo|bar[^_])$/i",
+ " /^(foo|bar[^_])$/i"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "7ebfb3f8fa6aefa4ff3d47961a58fe30be24431e"
+ "shas": "a73a7605d28b1fe2b09ce87d8db7426ea6295610..edcc26845e0ed493216f7b8ce1235e7a37ace55d"
}
,{
"testCaseDescription": "ruby-regex-replacement-test",
@@ -202,9 +230,20 @@
"filePaths": [
"regex.rb"
],
- "sha1": "7ebfb3f8fa6aefa4ff3d47961a58fe30be24431e",
+ "patch": [
+ "diff --git a/regex.rb b/regex.rb",
+ "index 42d4984..c801d61 100644",
+ "--- a/regex.rb",
+ "+++ b/regex.rb",
+ "@@ -1,3 +1,4 @@",
+ "-/^(foo|bar[^_])$/i",
+ "+%r/a/",
+ "+%rc>",
+ " /^(foo|bar[^_])$/i",
+ " /^(foo|bar[^_])$/i"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "693ff2b83628984af8cff14753f654f3fe4b5191"
+ "shas": "edcc26845e0ed493216f7b8ce1235e7a37ace55d..46655f4fd04784ed0fd995951c5f83018cc02d97"
}
,{
"testCaseDescription": "ruby-regex-delete-replacement-test",
@@ -233,9 +272,20 @@
"filePaths": [
"regex.rb"
],
- "sha1": "693ff2b83628984af8cff14753f654f3fe4b5191",
+ "patch": [
+ "diff --git a/regex.rb b/regex.rb",
+ "index c801d61..48e43a9 100644",
+ "--- a/regex.rb",
+ "+++ b/regex.rb",
+ "@@ -1,4 +1,3 @@",
+ "+/^(foo|bar[^_])$/i",
+ " %r/a/",
+ " %rc>",
+ "-/^(foo|bar[^_])$/i",
+ "-/^(foo|bar[^_])$/i"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "8fc7cf7faa4707eac8f85c2c8292186bf0cd17df"
+ "shas": "46655f4fd04784ed0fd995951c5f83018cc02d97..dd7c07f9f3797a03b8a34fbd1efdbc98b01d2e76"
}
,{
"testCaseDescription": "ruby-regex-delete-test",
@@ -264,9 +314,18 @@
"filePaths": [
"regex.rb"
],
- "sha1": "8fc7cf7faa4707eac8f85c2c8292186bf0cd17df",
+ "patch": [
+ "diff --git a/regex.rb b/regex.rb",
+ "index 48e43a9..b23927a 100644",
+ "--- a/regex.rb",
+ "+++ b/regex.rb",
+ "@@ -1,3 +1,2 @@",
+ "-/^(foo|bar[^_])$/i",
+ " %r/a/",
+ " %rc>"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "8244f427425657b3b9ea1aa243591cf3e0e44f1b"
+ "shas": "dd7c07f9f3797a03b8a34fbd1efdbc98b01d2e76..a9ee657f847f069d80fe4f52e9b1fb3bf991f26f"
}
,{
"testCaseDescription": "ruby-regex-delete-rest-test",
@@ -310,7 +369,15 @@
"filePaths": [
"regex.rb"
],
- "sha1": "8244f427425657b3b9ea1aa243591cf3e0e44f1b",
+ "patch": [
+ "diff --git a/regex.rb b/regex.rb",
+ "index b23927a..e69de29 100644",
+ "--- a/regex.rb",
+ "+++ b/regex.rb",
+ "@@ -1,2 +0,0 @@",
+ "-%r/a/",
+ "-%rc>"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "275c429c547953450d7c9bf531188b8f50e9295d"
+ "shas": "a9ee657f847f069d80fe4f52e9b1fb3bf991f26f..e8c4c9b4ba151237a0e88d5a650d34ee5a5a1b61"
}]
diff --git a/test/corpus/diff-summaries/ruby/relational-operator.json b/test/corpus/diff-summaries/ruby/relational-operator.json
index 99ad535f1..a27cc9234 100644
--- a/test/corpus/diff-summaries/ruby/relational-operator.json
+++ b/test/corpus/diff-summaries/ruby/relational-operator.json
@@ -55,9 +55,18 @@
"filePaths": [
"relational-operator.rb"
],
- "sha1": "ef97729fc1ce67c8c748ea440decb29ce2e8fb6e",
+ "patch": [
+ "diff --git a/relational-operator.rb b/relational-operator.rb",
+ "index e69de29..e2290b2 100644",
+ "--- a/relational-operator.rb",
+ "+++ b/relational-operator.rb",
+ "@@ -0,0 +1,3 @@",
+ "+x == y",
+ "+x != y",
+ "+x === y"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "724a9cb614befd72789dcd62cf7b0a9985dd9b23"
+ "shas": "0c8195a0d30149b84b53bc2c98687d24a787f4dd..a1f4def52826a2f5f35936ea4974cec5ea85e091"
}
,{
"testCaseDescription": "ruby-relational-operator-replacement-insert-test",
@@ -161,9 +170,24 @@
"filePaths": [
"relational-operator.rb"
],
- "sha1": "724a9cb614befd72789dcd62cf7b0a9985dd9b23",
+ "patch": [
+ "diff --git a/relational-operator.rb b/relational-operator.rb",
+ "index e2290b2..d547ce5 100644",
+ "--- a/relational-operator.rb",
+ "+++ b/relational-operator.rb",
+ "@@ -1,3 +1,9 @@",
+ "+x <=> y",
+ "+x =~ y",
+ "+x =! y",
+ "+x == y",
+ "+x != y",
+ "+x === y",
+ " x == y",
+ " x != y",
+ " x === y"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "57d4171a58d3565183f75619b4c044aa0e80c5c2"
+ "shas": "a1f4def52826a2f5f35936ea4974cec5ea85e091..a410e8475bcc3f55ccadce1c1de878e0f23137c8"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-insert-test",
@@ -207,9 +231,24 @@
"filePaths": [
"relational-operator.rb"
],
- "sha1": "57d4171a58d3565183f75619b4c044aa0e80c5c2",
+ "patch": [
+ "diff --git a/relational-operator.rb b/relational-operator.rb",
+ "index d547ce5..5849f29 100644",
+ "--- a/relational-operator.rb",
+ "+++ b/relational-operator.rb",
+ "@@ -1,6 +1,6 @@",
+ "-x <=> y",
+ "-x =~ y",
+ "-x =! y",
+ "+x == y",
+ "+x != y",
+ "+x === y",
+ " x == y",
+ " x != y",
+ " x === y"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "abfa3a152c9057cf2373a440079e39757782e9bb"
+ "shas": "a410e8475bcc3f55ccadce1c1de878e0f23137c8..863fa3c522169326664ae03b9d6fec02d4dd9eba"
}
,{
"testCaseDescription": "ruby-relational-operator-replacement-test",
@@ -253,9 +292,24 @@
"filePaths": [
"relational-operator.rb"
],
- "sha1": "abfa3a152c9057cf2373a440079e39757782e9bb",
+ "patch": [
+ "diff --git a/relational-operator.rb b/relational-operator.rb",
+ "index 5849f29..d547ce5 100644",
+ "--- a/relational-operator.rb",
+ "+++ b/relational-operator.rb",
+ "@@ -1,6 +1,6 @@",
+ "-x == y",
+ "-x != y",
+ "-x === y",
+ "+x <=> y",
+ "+x =~ y",
+ "+x =! y",
+ " x == y",
+ " x != y",
+ " x === y"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "92a1884a99d461f88a20c7ba0be8c3b850ce82cd"
+ "shas": "863fa3c522169326664ae03b9d6fec02d4dd9eba..d8b19e6874eeee4b5190a4ec83a8f106c9374626"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-replacement-test",
@@ -344,9 +398,27 @@
"filePaths": [
"relational-operator.rb"
],
- "sha1": "92a1884a99d461f88a20c7ba0be8c3b850ce82cd",
+ "patch": [
+ "diff --git a/relational-operator.rb b/relational-operator.rb",
+ "index d547ce5..ac1eb5d 100644",
+ "--- a/relational-operator.rb",
+ "+++ b/relational-operator.rb",
+ "@@ -1,9 +1,6 @@",
+ "-x <=> y",
+ "-x =~ y",
+ "-x =! y",
+ "-x == y",
+ "-x != y",
+ "-x === y",
+ " x == y",
+ " x != y",
+ " x === y",
+ "+x <=> y",
+ "+x =~ y",
+ "+x =! y"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e4851a23d5aa5cbe144dff6b48cb6c33c51fd7e1"
+ "shas": "d8b19e6874eeee4b5190a4ec83a8f106c9374626..26c6f1f20d765f5c209e74a29bb714b6b7aae5b7"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-test",
@@ -405,9 +477,21 @@
"filePaths": [
"relational-operator.rb"
],
- "sha1": "e4851a23d5aa5cbe144dff6b48cb6c33c51fd7e1",
+ "patch": [
+ "diff --git a/relational-operator.rb b/relational-operator.rb",
+ "index ac1eb5d..8180103 100644",
+ "--- a/relational-operator.rb",
+ "+++ b/relational-operator.rb",
+ "@@ -1,6 +1,3 @@",
+ "-x == y",
+ "-x != y",
+ "-x === y",
+ " x <=> y",
+ " x =~ y",
+ " x =! y"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "3ace56632c61e59046865dee72b13029a9a1b0b2"
+ "shas": "26c6f1f20d765f5c209e74a29bb714b6b7aae5b7..17932b7d6a37caa52201ba5309a86f228fb81493"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-rest-test",
@@ -466,7 +550,16 @@
"filePaths": [
"relational-operator.rb"
],
- "sha1": "3ace56632c61e59046865dee72b13029a9a1b0b2",
+ "patch": [
+ "diff --git a/relational-operator.rb b/relational-operator.rb",
+ "index 8180103..e69de29 100644",
+ "--- a/relational-operator.rb",
+ "+++ b/relational-operator.rb",
+ "@@ -1,3 +0,0 @@",
+ "-x <=> y",
+ "-x =~ y",
+ "-x =! y"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "b5ca633b949a2227913a944093e291dd78724130"
+ "shas": "17932b7d6a37caa52201ba5309a86f228fb81493..cc9a4a6fa2a1c65983250a900daf6501538b4cd8"
}]
diff --git a/test/corpus/diff-summaries/ruby/rescue-empty.json b/test/corpus/diff-summaries/ruby/rescue-empty.json
new file mode 100644
index 000000000..f8de14333
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/rescue-empty.json
@@ -0,0 +1,363 @@
+[{
+ "testCaseDescription": "ruby-rescue-empty-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-empty.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-empty.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index e69de29..5b4fe96 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -0,0 +1,4 @@",
+ "+begin",
+ "+ foo",
+ "+rescue",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "759d04410984c3b7b0c25212ef74986fba96a76f..48354aa04a6e30841aa1b0ba10f934aba9d877bb"
+}
+,{
+ "testCaseDescription": "ruby-rescue-empty-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-empty.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 9,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-empty.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index 5b4fe96..d74e034 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,4 +1,13 @@",
+ " begin",
+ " foo",
+ " rescue",
+ "+ bar",
+ "+end",
+ "+begin",
+ "+ foo",
+ "+rescue",
+ "+end",
+ "+begin",
+ "+ foo",
+ "+rescue",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "48354aa04a6e30841aa1b0ba10f934aba9d877bb..ffef7ac3bf0c394c4b150fc38e7d84bcc0116a90"
+}
+,{
+ "testCaseDescription": "ruby-rescue-empty-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-empty.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' identifier in a rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-empty.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index d74e034..afdc934 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,7 +1,6 @@",
+ " begin",
+ " foo",
+ " rescue",
+ "- bar",
+ " end",
+ " begin",
+ " foo"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "ffef7ac3bf0c394c4b150fc38e7d84bcc0116a90..dbf6e3412604ec2bdd35156d5b9ea52e220c5464"
+}
+,{
+ "testCaseDescription": "ruby-rescue-empty-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-empty.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar' identifier in a rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-empty.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index afdc934..d74e034 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,6 +1,7 @@",
+ " begin",
+ " foo",
+ " rescue",
+ "+ bar",
+ " end",
+ " begin",
+ " foo"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "dbf6e3412604ec2bdd35156d5b9ea52e220c5464..3df29e631fd2d388ec3f1aaca908e6b1945e7481"
+}
+,{
+ "testCaseDescription": "ruby-rescue-empty-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-empty.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 9,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 9,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-empty.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index d74e034..f8a72a7 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,13 +1,9 @@",
+ " begin",
+ " foo",
+ " rescue",
+ "- bar",
+ "-end",
+ "-begin",
+ "- foo",
+ "-rescue",
+ " end",
+ " begin",
+ " foo",
+ " rescue",
+ "+ bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "3df29e631fd2d388ec3f1aaca908e6b1945e7481..70c02489eb082cc5dd59b661bae79c8df0997ea9"
+}
+,{
+ "testCaseDescription": "ruby-rescue-empty-delete-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-empty.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-empty.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index f8a72a7..17dffb3 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,9 +1,5 @@",
+ " begin",
+ " foo",
+ " rescue",
+ "-end",
+ "-begin",
+ "- foo",
+ "-rescue",
+ " bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "70c02489eb082cc5dd59b661bae79c8df0997ea9..7a71af57bd14a190b95e66a932a58c1f64b3983b"
+}
+,{
+ "testCaseDescription": "ruby-rescue-empty-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-empty.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-empty.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index 17dffb3..e69de29 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,5 +0,0 @@",
+ "-begin",
+ "- foo",
+ "-rescue",
+ "- bar",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "7a71af57bd14a190b95e66a932a58c1f64b3983b..e805bb575511867c24e67d81ccae909f2668e660"
+}]
diff --git a/test/corpus/diff-summaries/ruby/rescue-last-ex.json b/test/corpus/diff-summaries/ruby/rescue-last-ex.json
new file mode 100644
index 000000000..9cc49bdc4
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/rescue-last-ex.json
@@ -0,0 +1,363 @@
+[{
+ "testCaseDescription": "ruby-rescue-last-ex-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index e69de29..a5dbb28 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -0,0 +1,4 @@",
+ "+begin",
+ "+ foo",
+ "+rescue Error => x",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "e805bb575511867c24e67d81ccae909f2668e660..57fbaa6c0752b39141df6d2229a40d52ab46eec2"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 9,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index a5dbb28..9c0bf85 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,4 +1,13 @@",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "+ bar",
+ "+end",
+ "+begin",
+ "+ foo",
+ "+rescue Error => x",
+ "+end",
+ "+begin",
+ "+ foo",
+ "+rescue Error => x",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "57fbaa6c0752b39141df6d2229a40d52ab46eec2..1abc809f7c5f4bce8b655282c1a89c80acdb4719"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' identifier in the 'Error, x' rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index 9c0bf85..e6fe0ab 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,7 +1,6 @@",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "- bar",
+ " end",
+ " begin",
+ " foo"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1abc809f7c5f4bce8b655282c1a89c80acdb4719..4d3835c45aaafa64cf2ea5d23c0e0a7ca25f50ba"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar' identifier in the 'Error, x' rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index e6fe0ab..9c0bf85 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,6 +1,7 @@",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "+ bar",
+ " end",
+ " begin",
+ " foo"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "4d3835c45aaafa64cf2ea5d23c0e0a7ca25f50ba..1a1c77e9e42914a1ec12b746fa9bfaf045f39be6"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 9,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 9,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index 9c0bf85..23c7c1b 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,13 +1,9 @@",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "- bar",
+ "-end",
+ "-begin",
+ "- foo",
+ "-rescue Error => x",
+ " end",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "+ bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1a1c77e9e42914a1ec12b746fa9bfaf045f39be6..fba897776dd4e1be1f36e4a3685fcdb77e2fdd77"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-delete-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index 23c7c1b..c247b6d 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,9 +1,5 @@",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "-end",
+ "-begin",
+ "- foo",
+ "-rescue Error => x",
+ " bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "fba897776dd4e1be1f36e4a3685fcdb77e2fdd77..c605c98f25261242ec2e73cc56004de8524dea2e"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index c247b6d..e69de29 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,5 +0,0 @@",
+ "-begin",
+ "- foo",
+ "-rescue Error => x",
+ "- bar",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c605c98f25261242ec2e73cc56004de8524dea2e..875face60282636c8ba6fbd9db4a50c6b8b38fd2"
+}]
diff --git a/test/corpus/diff-summaries/javascript/object-with-methods.json b/test/corpus/diff-summaries/ruby/rescue-modifier.json
similarity index 50%
rename from test/corpus/diff-summaries/javascript/object-with-methods.json
rename to test/corpus/diff-summaries/ruby/rescue-modifier.json
index d975d5aa3..741dbd275 100644
--- a/test/corpus/diff-summaries/javascript/object-with-methods.json
+++ b/test/corpus/diff-summaries/ruby/rescue-modifier.json
@@ -1,8 +1,8 @@
[{
- "testCaseDescription": "javascript-objects-with-methods-insert-test",
+ "testCaseDescription": "ruby-rescue-modifier-insert-test",
"expectedResult": {
"changes": {
- "objects-with-methods.js": [
+ "rescue-modifier.rb": [
{
"span": {
"insert": {
@@ -12,28 +12,35 @@
],
"end": [
1,
- 32
+ 15
]
}
},
- "summary": "Added the '{ add }' object"
+ "summary": "Added the 'foo' rescue modifier"
}
]
},
"errors": {}
},
"filePaths": [
- "objects-with-methods.js"
+ "rescue-modifier.rb"
],
- "sha1": "a70334394db6019d12e7b0784152b7931be8a143",
- "gitDir": "test/corpus/repos/javascript",
- "sha2": "a0fd17b1857723ef6273a44f907cda57e37974ac"
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index e69de29..b0cea1a 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -0,0 +1 @@",
+ "+foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "dbbf1ed8a8cafe556ea468af463f118f3ca0f4ba..ee8d8559b436b4434abf6fb62e720fd2b2e25e67"
}
,{
- "testCaseDescription": "javascript-objects-with-methods-replacement-insert-test",
+ "testCaseDescription": "ruby-rescue-modifier-replacement-insert-test",
"expectedResult": {
"changes": {
- "objects-with-methods.js": [
+ "rescue-modifier.rb": [
{
"span": {
"insert": {
@@ -43,11 +50,11 @@
],
"end": [
1,
- 37
+ 17
]
}
},
- "summary": "Added the '{ subtract }' object"
+ "summary": "Added the 'foo' rescue modifier"
},
{
"span": {
@@ -58,114 +65,143 @@
],
"end": [
2,
- 32
+ 15
]
}
},
- "summary": "Added the '{ add }' object"
+ "summary": "Added the 'foo' rescue modifier"
}
]
},
"errors": {}
},
"filePaths": [
- "objects-with-methods.js"
+ "rescue-modifier.rb"
],
- "sha1": "a0fd17b1857723ef6273a44f907cda57e37974ac",
- "gitDir": "test/corpus/repos/javascript",
- "sha2": "ee9e102b7b70e841506c83d6775a06fbef86cc90"
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index b0cea1a..79b1f6a 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1 +1,3 @@",
+ "+foo rescue false",
+ "+foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "ee8d8559b436b4434abf6fb62e720fd2b2e25e67..f757d66e78f7d4e6497ce72a70017e34180e6ed7"
}
,{
- "testCaseDescription": "javascript-objects-with-methods-delete-insert-test",
+ "testCaseDescription": "ruby-rescue-modifier-delete-insert-test",
"expectedResult": {
"changes": {
- "objects-with-methods.js": [
+ "rescue-modifier.rb": [
{
"span": {
"replace": [
{
"start": [
1,
- 3
+ 1
],
"end": [
1,
- 11
+ 17
]
},
{
"start": [
1,
- 3
+ 1
],
"end": [
1,
- 6
+ 15
]
}
]
},
- "summary": "Replaced the 'subtract' identifier with the 'add' identifier in the add method"
+ "summary": "Replaced the 'foo' rescue modifier with the 'foo' rescue modifier"
}
]
},
"errors": {}
},
"filePaths": [
- "objects-with-methods.js"
+ "rescue-modifier.rb"
],
- "sha1": "ee9e102b7b70e841506c83d6775a06fbef86cc90",
- "gitDir": "test/corpus/repos/javascript",
- "sha2": "cdc665ab83bdfbe48d09516419efbc8293eceb28"
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index 79b1f6a..f59c8c2 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1,3 +1,3 @@",
+ "-foo rescue false",
+ "+foo rescue nil",
+ " foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "f757d66e78f7d4e6497ce72a70017e34180e6ed7..48cf3c8ae9539479ada31649b7907f45750d3587"
}
,{
- "testCaseDescription": "javascript-objects-with-methods-replacement-test",
+ "testCaseDescription": "ruby-rescue-modifier-replacement-test",
"expectedResult": {
"changes": {
- "objects-with-methods.js": [
+ "rescue-modifier.rb": [
{
"span": {
"replace": [
{
"start": [
1,
- 3
+ 1
],
"end": [
1,
- 6
+ 15
]
},
{
"start": [
1,
- 3
+ 1
],
"end": [
1,
- 11
+ 17
]
}
]
},
- "summary": "Replaced the 'add' identifier with the 'subtract' identifier in the subtract method"
+ "summary": "Replaced the 'foo' rescue modifier with the 'foo' rescue modifier"
}
]
},
"errors": {}
},
"filePaths": [
- "objects-with-methods.js"
+ "rescue-modifier.rb"
],
- "sha1": "cdc665ab83bdfbe48d09516419efbc8293eceb28",
- "gitDir": "test/corpus/repos/javascript",
- "sha2": "29c25335a64f0afd24c97afe81528d18081986f6"
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index f59c8c2..79b1f6a 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1,3 +1,3 @@",
+ "-foo rescue nil",
+ "+foo rescue false",
+ " foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "48cf3c8ae9539479ada31649b7907f45750d3587..e27305bea14543e812e35efdfad8e15916b44bce"
}
,{
- "testCaseDescription": "javascript-objects-with-methods-delete-replacement-test",
+ "testCaseDescription": "ruby-rescue-modifier-delete-replacement-test",
"expectedResult": {
"changes": {
- "objects-with-methods.js": [
+ "rescue-modifier.rb": [
{
"span": {
"delete": {
@@ -175,11 +211,11 @@
],
"end": [
1,
- 37
+ 17
]
}
},
- "summary": "Deleted the '{ subtract }' object"
+ "summary": "Deleted the 'foo' rescue modifier"
},
{
"span": {
@@ -190,11 +226,11 @@
],
"end": [
2,
- 32
+ 15
]
}
},
- "summary": "Deleted the '{ add }' object"
+ "summary": "Deleted the 'foo' rescue modifier"
},
{
"span": {
@@ -205,28 +241,38 @@
],
"end": [
2,
- 37
+ 17
]
}
},
- "summary": "Added the '{ subtract }' object"
+ "summary": "Added the 'foo' rescue modifier"
}
]
},
"errors": {}
},
"filePaths": [
- "objects-with-methods.js"
+ "rescue-modifier.rb"
],
- "sha1": "29c25335a64f0afd24c97afe81528d18081986f6",
- "gitDir": "test/corpus/repos/javascript",
- "sha2": "4dcf79e103e6c92f8c96a1774535237b7b162817"
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index 79b1f6a..509bcea 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1,3 +1,2 @@",
+ "-foo rescue false",
+ "-foo rescue nil",
+ " foo rescue nil",
+ "+foo rescue false"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "e27305bea14543e812e35efdfad8e15916b44bce..8448399194931991c532e1431d5bb57feec7e9d2"
}
,{
- "testCaseDescription": "javascript-objects-with-methods-delete-test",
+ "testCaseDescription": "ruby-rescue-modifier-delete-test",
"expectedResult": {
"changes": {
- "objects-with-methods.js": [
+ "rescue-modifier.rb": [
{
"span": {
"delete": {
@@ -236,28 +282,36 @@
],
"end": [
1,
- 32
+ 15
]
}
},
- "summary": "Deleted the '{ add }' object"
+ "summary": "Deleted the 'foo' rescue modifier"
}
]
},
"errors": {}
},
"filePaths": [
- "objects-with-methods.js"
+ "rescue-modifier.rb"
],
- "sha1": "4dcf79e103e6c92f8c96a1774535237b7b162817",
- "gitDir": "test/corpus/repos/javascript",
- "sha2": "f36d9d7eb61a638531a82fbcac3c8d2093f908a1"
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index 509bcea..c36274a 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1,2 +1 @@",
+ "-foo rescue nil",
+ " foo rescue false"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "8448399194931991c532e1431d5bb57feec7e9d2..0aa3073a2d457a147b4ce034ab0576694ff7ed6d"
}
,{
- "testCaseDescription": "javascript-objects-with-methods-delete-rest-test",
+ "testCaseDescription": "ruby-rescue-modifier-delete-rest-test",
"expectedResult": {
"changes": {
- "objects-with-methods.js": [
+ "rescue-modifier.rb": [
{
"span": {
"delete": {
@@ -267,20 +321,27 @@
],
"end": [
1,
- 37
+ 17
]
}
},
- "summary": "Deleted the '{ subtract }' object"
+ "summary": "Deleted the 'foo' rescue modifier"
}
]
},
"errors": {}
},
"filePaths": [
- "objects-with-methods.js"
+ "rescue-modifier.rb"
],
- "sha1": "f36d9d7eb61a638531a82fbcac3c8d2093f908a1",
- "gitDir": "test/corpus/repos/javascript",
- "sha2": "0ae7d23e3b8ca76072bab79fd0258880ca4413d5"
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index c36274a..e69de29 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1 +0,0 @@",
+ "-foo rescue false"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "0aa3073a2d457a147b4ce034ab0576694ff7ed6d..89be77a7b4f5ee9670276a33a97a6aa3941c9cfb"
}]
diff --git a/test/corpus/diff-summaries/ruby/rescue-modifier2.json b/test/corpus/diff-summaries/ruby/rescue-modifier2.json
new file mode 100644
index 000000000..013965be2
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/rescue-modifier2.json
@@ -0,0 +1,347 @@
+[{
+ "testCaseDescription": "ruby-rescue-modifier2-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index e69de29..b0cea1a 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -0,0 +1 @@",
+ "+foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "89be77a7b4f5ee9670276a33a97a6aa3941c9cfb..55cdbc8c69ef00db47f231d904f083eb28f50160"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'bar' rescue modifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index b0cea1a..595bf2e 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1 +1,3 @@",
+ "+bar rescue nil",
+ "+foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "55cdbc8c69ef00db47f231d904f083eb28f50160..198f5f3b96b3f405c1ff2081a511fac17edc7c91"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'bar' identifier with the 'foo' identifier in the 'rescue foo' modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index 595bf2e..f59c8c2 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1,3 +1,3 @@",
+ "-bar rescue nil",
+ "+foo rescue nil",
+ " foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "198f5f3b96b3f405c1ff2081a511fac17edc7c91..1e6f032a4125e945220103becbd30842264ab52e"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'foo' identifier with the 'bar' identifier in the 'rescue bar' modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index f59c8c2..595bf2e 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1,3 +1,3 @@",
+ "-foo rescue nil",
+ "+bar rescue nil",
+ " foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1e6f032a4125e945220103becbd30842264ab52e..a666824e8c4d5b66c6d27e6a0246b63a3042b7a0"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' rescue modifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' rescue modifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'bar' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index 595bf2e..0d0f274 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1,3 +1,2 @@",
+ "-bar rescue nil",
+ "-foo rescue nil",
+ " foo rescue nil",
+ "+bar rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "a666824e8c4d5b66c6d27e6a0246b63a3042b7a0..14d5975cd55f2b7d27ce40f3491786b5644c10a6"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-delete-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index 0d0f274..f7b54a5 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1,2 +1 @@",
+ "-foo rescue nil",
+ " bar rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "14d5975cd55f2b7d27ce40f3491786b5644c10a6..0446bcdbd6fc1e4f75ecdd984d9428c2d82e4c2a"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index f7b54a5..e69de29 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1 +0,0 @@",
+ "-bar rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "0446bcdbd6fc1e4f75ecdd984d9428c2d82e4c2a..375e457b7d8886bdbdb8b3e131a0c001d20ac41c"
+}]
diff --git a/test/corpus/diff-summaries/ruby/rescue.json b/test/corpus/diff-summaries/ruby/rescue.json
new file mode 100644
index 000000000..cea57a6b7
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/rescue.json
@@ -0,0 +1,246 @@
+[{
+ "testCaseDescription": "ruby-rescue-setup-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index e69de29..dbcd28c 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -0,0 +1,3 @@",
+ "+begin",
+ "+ foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "7d242e1a703020b3d44a44dfca02698401fd5888..c1c1d85a11ab375b2a5cecfa753ce55794695893"
+}
+,{
+ "testCaseDescription": "ruby-rescue-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 4,
+ 1
+ ]
+ }
+ },
+ "summary": "Added the 'x' rescue block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index dbcd28c..fd1f6b9 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -1,3 +1,4 @@",
+ " begin",
+ " foo",
+ "+rescue x",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c1c1d85a11ab375b2a5cecfa753ce55794695893..d2e5d09c09142af88df3e14e001d4f8b3c50400b"
+}
+,{
+ "testCaseDescription": "ruby-rescue-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar' identifier in the 'x' rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index fd1f6b9..e83ea4c 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -1,4 +1,5 @@",
+ " begin",
+ " foo",
+ " rescue x",
+ "+ bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d2e5d09c09142af88df3e14e001d4f8b3c50400b..29ff959d72ec67c93481eb566a450a91a5fdb5e3"
+}
+,{
+ "testCaseDescription": "ruby-rescue-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' identifier in the 'x' rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index e83ea4c..fd1f6b9 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -1,5 +1,4 @@",
+ " begin",
+ " foo",
+ " rescue x",
+ "- bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "29ff959d72ec67c93481eb566a450a91a5fdb5e3..1e5060ad564b33df252b8ebe36db76da23c71d11"
+}
+,{
+ "testCaseDescription": "ruby-rescue-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 4,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the 'x' rescue block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index fd1f6b9..dbcd28c 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -1,4 +1,3 @@",
+ " begin",
+ " foo",
+ "-rescue x",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1e5060ad564b33df252b8ebe36db76da23c71d11..742f43f551628274941ad509b4d47a9467022038"
+}
+,{
+ "testCaseDescription": "ruby-rescue-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index dbcd28c..e69de29 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -1,3 +0,0 @@",
+ "-begin",
+ "- foo",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "742f43f551628274941ad509b4d47a9467022038..759d04410984c3b7b0c25212ef74986fba96a76f"
+}]
diff --git a/test/corpus/diff-summaries/ruby/return.json b/test/corpus/diff-summaries/ruby/return.json
index cc9c90ea0..8c61d01fc 100644
--- a/test/corpus/diff-summaries/ruby/return.json
+++ b/test/corpus/diff-summaries/ruby/return.json
@@ -25,9 +25,16 @@
"filePaths": [
"return.rb"
],
- "sha1": "932ab2e771298de02435e6560b092f44116db759",
+ "patch": [
+ "diff --git a/return.rb b/return.rb",
+ "index e69de29..c09b956 100644",
+ "--- a/return.rb",
+ "+++ b/return.rb",
+ "@@ -0,0 +1 @@",
+ "+return foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "eccd61ff2d7e39eece6034a0f61e76419caa4b26"
+ "shas": "b9eed5bd1eb6aacf2a54e334b4297955018776a8..bea7290ff72c82de8db2a0c9ae8eae0095f9f133"
}
,{
"testCaseDescription": "ruby-return-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"return.rb"
],
- "sha1": "eccd61ff2d7e39eece6034a0f61e76419caa4b26",
+ "patch": [
+ "diff --git a/return.rb b/return.rb",
+ "index c09b956..03af74c 100644",
+ "--- a/return.rb",
+ "+++ b/return.rb",
+ "@@ -1 +1,3 @@",
+ "+return",
+ "+return foo",
+ " return foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e8e3916dc6370cc30aa380c097b96b0f35e7607f"
+ "shas": "bea7290ff72c82de8db2a0c9ae8eae0095f9f133..328345c3ed837afd421202db539c4e8b374e4877"
}
,{
"testCaseDescription": "ruby-return-delete-insert-test",
@@ -102,9 +118,19 @@
"filePaths": [
"return.rb"
],
- "sha1": "e8e3916dc6370cc30aa380c097b96b0f35e7607f",
+ "patch": [
+ "diff --git a/return.rb b/return.rb",
+ "index 03af74c..199a182 100644",
+ "--- a/return.rb",
+ "+++ b/return.rb",
+ "@@ -1,3 +1,3 @@",
+ "-return",
+ "+return foo",
+ " return foo",
+ " return foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "5f8e3137aa3c52ec02dc29d41327038979923564"
+ "shas": "328345c3ed837afd421202db539c4e8b374e4877..564f0138ad63d31ca573e410cd1f69143df79e04"
}
,{
"testCaseDescription": "ruby-return-replacement-test",
@@ -133,9 +159,19 @@
"filePaths": [
"return.rb"
],
- "sha1": "5f8e3137aa3c52ec02dc29d41327038979923564",
+ "patch": [
+ "diff --git a/return.rb b/return.rb",
+ "index 199a182..03af74c 100644",
+ "--- a/return.rb",
+ "+++ b/return.rb",
+ "@@ -1,3 +1,3 @@",
+ "-return foo",
+ "+return",
+ " return foo",
+ " return foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "95f700610a1f902afd8939ce6655d36c61dcfd15"
+ "shas": "564f0138ad63d31ca573e410cd1f69143df79e04..daf6b77e4ee816ceef89bc43e56baa339ca2708f"
}
,{
"testCaseDescription": "ruby-return-delete-replacement-test",
@@ -194,9 +230,19 @@
"filePaths": [
"return.rb"
],
- "sha1": "95f700610a1f902afd8939ce6655d36c61dcfd15",
+ "patch": [
+ "diff --git a/return.rb b/return.rb",
+ "index 03af74c..09606e9 100644",
+ "--- a/return.rb",
+ "+++ b/return.rb",
+ "@@ -1,3 +1,2 @@",
+ "-return",
+ "-return foo",
+ " return foo",
+ "+return"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "71a7f4e9cc7238c316d61c724882b35e42fca6b3"
+ "shas": "daf6b77e4ee816ceef89bc43e56baa339ca2708f..837ad22ea13472d087a09e873830453c9e7bf89d"
}
,{
"testCaseDescription": "ruby-return-delete-test",
@@ -225,9 +271,17 @@
"filePaths": [
"return.rb"
],
- "sha1": "71a7f4e9cc7238c316d61c724882b35e42fca6b3",
+ "patch": [
+ "diff --git a/return.rb b/return.rb",
+ "index 09606e9..a09c863 100644",
+ "--- a/return.rb",
+ "+++ b/return.rb",
+ "@@ -1,2 +1 @@",
+ "-return foo",
+ " return"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "cda01a8f0c578e8c76906624ad55372b8e30cb44"
+ "shas": "837ad22ea13472d087a09e873830453c9e7bf89d..76fdd8535cd04dcae0eef2cddafc74d3176932f6"
}
,{
"testCaseDescription": "ruby-return-delete-rest-test",
@@ -256,7 +310,14 @@
"filePaths": [
"return.rb"
],
- "sha1": "cda01a8f0c578e8c76906624ad55372b8e30cb44",
+ "patch": [
+ "diff --git a/return.rb b/return.rb",
+ "index a09c863..e69de29 100644",
+ "--- a/return.rb",
+ "+++ b/return.rb",
+ "@@ -1 +0,0 @@",
+ "-return"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "9b31b02e831a9ab3366e95bcb9f6399451d97d76"
+ "shas": "76fdd8535cd04dcae0eef2cddafc74d3176932f6..e9e47a7e8dfaea6fade11176891263b27322f29d"
}]
diff --git a/test/corpus/diff-summaries/ruby/string.json b/test/corpus/diff-summaries/ruby/string.json
index 133709f13..81f776c97 100644
--- a/test/corpus/diff-summaries/ruby/string.json
+++ b/test/corpus/diff-summaries/ruby/string.json
@@ -40,9 +40,17 @@
"filePaths": [
"string.rb"
],
- "sha1": "1da7c8ba79becf9a9b091384779dc9bf9ab0136b",
+ "patch": [
+ "diff --git a/string.rb b/string.rb",
+ "index e69de29..8d1b50a 100644",
+ "--- a/string.rb",
+ "+++ b/string.rb",
+ "@@ -0,0 +1,2 @@",
+ "+''",
+ "+'foo with \"bar\"'"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "d0bcc2781177a044bc6701ab731b9e633878e350"
+ "shas": "59e2edbe041b887605acb7a535fcceacb50d82a3..e65d8c9000cf029d28a1673f020f37eb43dfd4be"
}
,{
"testCaseDescription": "ruby-string-replacement-insert-test",
@@ -116,9 +124,21 @@
"filePaths": [
"string.rb"
],
- "sha1": "d0bcc2781177a044bc6701ab731b9e633878e350",
+ "patch": [
+ "diff --git a/string.rb b/string.rb",
+ "index 8d1b50a..f1597ee 100644",
+ "--- a/string.rb",
+ "+++ b/string.rb",
+ "@@ -1,2 +1,6 @@",
+ "+\"\"",
+ "+\"bar with 'foo'\"",
+ "+''",
+ "+'foo with \"bar\"'",
+ " ''",
+ " 'foo with \"bar\"'"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "3258b4998ff47a27fce961068c99cd79bf6a4242"
+ "shas": "e65d8c9000cf029d28a1673f020f37eb43dfd4be..ce8dd8c8d416851edf4cda7e77c90f7c84706213"
}
,{
"testCaseDescription": "ruby-string-delete-insert-test",
@@ -186,9 +206,22 @@
"filePaths": [
"string.rb"
],
- "sha1": "3258b4998ff47a27fce961068c99cd79bf6a4242",
+ "patch": [
+ "diff --git a/string.rb b/string.rb",
+ "index f1597ee..6158c1a 100644",
+ "--- a/string.rb",
+ "+++ b/string.rb",
+ "@@ -1,5 +1,5 @@",
+ "-\"\"",
+ "-\"bar with 'foo'\"",
+ "+''",
+ "+'foo with \"bar\"'",
+ " ''",
+ " 'foo with \"bar\"'",
+ " ''"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "c3d587eedf675d92b046d5da16471df538004878"
+ "shas": "ce8dd8c8d416851edf4cda7e77c90f7c84706213..052fa225974c071dad866d796ddde1aecf5b0b35"
}
,{
"testCaseDescription": "ruby-string-replacement-test",
@@ -256,9 +289,22 @@
"filePaths": [
"string.rb"
],
- "sha1": "c3d587eedf675d92b046d5da16471df538004878",
+ "patch": [
+ "diff --git a/string.rb b/string.rb",
+ "index 6158c1a..f1597ee 100644",
+ "--- a/string.rb",
+ "+++ b/string.rb",
+ "@@ -1,5 +1,5 @@",
+ "-''",
+ "-'foo with \"bar\"'",
+ "+\"\"",
+ "+\"bar with 'foo'\"",
+ " ''",
+ " 'foo with \"bar\"'",
+ " ''"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "5b2dca9c2599211adec25539453d649b3b0e1826"
+ "shas": "052fa225974c071dad866d796ddde1aecf5b0b35..7fbee64365bc046de4be39070d47b51793272da8"
}
,{
"testCaseDescription": "ruby-string-delete-replacement-test",
@@ -362,9 +408,23 @@
"filePaths": [
"string.rb"
],
- "sha1": "5b2dca9c2599211adec25539453d649b3b0e1826",
+ "patch": [
+ "diff --git a/string.rb b/string.rb",
+ "index f1597ee..b8be05c 100644",
+ "--- a/string.rb",
+ "+++ b/string.rb",
+ "@@ -1,6 +1,4 @@",
+ "-\"\"",
+ "-\"bar with 'foo'\"",
+ "-''",
+ "-'foo with \"bar\"'",
+ " ''",
+ " 'foo with \"bar\"'",
+ "+\"\"",
+ "+\"bar with 'foo'\""
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "03c0576c75db435100dd6b1ba5f905e922beac8f"
+ "shas": "7fbee64365bc046de4be39070d47b51793272da8..a54602000f3a38376ca4a677e1e0fe0da4a42275"
}
,{
"testCaseDescription": "ruby-string-delete-test",
@@ -408,9 +468,19 @@
"filePaths": [
"string.rb"
],
- "sha1": "03c0576c75db435100dd6b1ba5f905e922beac8f",
+ "patch": [
+ "diff --git a/string.rb b/string.rb",
+ "index b8be05c..83e4a68 100644",
+ "--- a/string.rb",
+ "+++ b/string.rb",
+ "@@ -1,4 +1,2 @@",
+ "-''",
+ "-'foo with \"bar\"'",
+ " \"\"",
+ " \"bar with 'foo'\""
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "5d13167acb02fe329fccaaeb6ce960670c82b435"
+ "shas": "a54602000f3a38376ca4a677e1e0fe0da4a42275..133025dbfa9e5e2089ca6bb7fce8001446d7dee3"
}
,{
"testCaseDescription": "ruby-string-delete-rest-test",
@@ -454,7 +524,15 @@
"filePaths": [
"string.rb"
],
- "sha1": "5d13167acb02fe329fccaaeb6ce960670c82b435",
+ "patch": [
+ "diff --git a/string.rb b/string.rb",
+ "index 83e4a68..e69de29 100644",
+ "--- a/string.rb",
+ "+++ b/string.rb",
+ "@@ -1,2 +0,0 @@",
+ "-\"\"",
+ "-\"bar with 'foo'\""
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "27c8bb9ed1adb160824505aa87bcb49fd2bd0606"
+ "shas": "133025dbfa9e5e2089ca6bb7fce8001446d7dee3..2505617f30ca311da1378227cbf6a13d83647b91"
}]
diff --git a/test/corpus/diff-summaries/ruby/subshell.json b/test/corpus/diff-summaries/ruby/subshell.json
index 80eaf2931..051bd4a85 100644
--- a/test/corpus/diff-summaries/ruby/subshell.json
+++ b/test/corpus/diff-summaries/ruby/subshell.json
@@ -25,9 +25,16 @@
"filePaths": [
"subshell.rb"
],
- "sha1": "4cf0b1c84b725b7ecea2d0e2524d4aa83e9aa9f0",
+ "patch": [
+ "diff --git a/subshell.rb b/subshell.rb",
+ "index e69de29..169f84d 100644",
+ "--- a/subshell.rb",
+ "+++ b/subshell.rb",
+ "@@ -0,0 +1 @@",
+ "+`ls -la`"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "20eb2d66b4a9fa812951035a462e2b8f353431ff"
+ "shas": "f8cc3489b25f8d1857452648c25c51084dbdbdb9..522071b01d711758caecf86fae864d7a5e5e190c"
}
,{
"testCaseDescription": "ruby-subshell-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"subshell.rb"
],
- "sha1": "20eb2d66b4a9fa812951035a462e2b8f353431ff",
+ "patch": [
+ "diff --git a/subshell.rb b/subshell.rb",
+ "index 169f84d..4b279f6 100644",
+ "--- a/subshell.rb",
+ "+++ b/subshell.rb",
+ "@@ -1 +1,3 @@",
+ "+`git status`",
+ "+`ls -la`",
+ " `ls -la`"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "fdb9f2acfb3ed9873e84f15d9074908fe0185182"
+ "shas": "522071b01d711758caecf86fae864d7a5e5e190c..8339afa687e64dabdb372ff0b27bb39f832a1d02"
}
,{
"testCaseDescription": "ruby-subshell-delete-insert-test",
@@ -114,9 +130,19 @@
"filePaths": [
"subshell.rb"
],
- "sha1": "fdb9f2acfb3ed9873e84f15d9074908fe0185182",
+ "patch": [
+ "diff --git a/subshell.rb b/subshell.rb",
+ "index 4b279f6..6781ff3 100644",
+ "--- a/subshell.rb",
+ "+++ b/subshell.rb",
+ "@@ -1,3 +1,3 @@",
+ "-`git status`",
+ "+`ls -la`",
+ " `ls -la`",
+ " `ls -la`"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "2fa537418ba3d387dce14ef9c763e45d4c655b74"
+ "shas": "8339afa687e64dabdb372ff0b27bb39f832a1d02..c719966658d8f95beafc1b182efd507251268a5b"
}
,{
"testCaseDescription": "ruby-subshell-replacement-test",
@@ -157,9 +183,19 @@
"filePaths": [
"subshell.rb"
],
- "sha1": "2fa537418ba3d387dce14ef9c763e45d4c655b74",
+ "patch": [
+ "diff --git a/subshell.rb b/subshell.rb",
+ "index 6781ff3..4b279f6 100644",
+ "--- a/subshell.rb",
+ "+++ b/subshell.rb",
+ "@@ -1,3 +1,3 @@",
+ "-`ls -la`",
+ "+`git status`",
+ " `ls -la`",
+ " `ls -la`"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "ad62044aa63938576393977e95062643f6197e16"
+ "shas": "c719966658d8f95beafc1b182efd507251268a5b..611fa19dd10019ef47b3d7477c12855fe89177f2"
}
,{
"testCaseDescription": "ruby-subshell-delete-replacement-test",
@@ -218,9 +254,19 @@
"filePaths": [
"subshell.rb"
],
- "sha1": "ad62044aa63938576393977e95062643f6197e16",
+ "patch": [
+ "diff --git a/subshell.rb b/subshell.rb",
+ "index 4b279f6..c695b4c 100644",
+ "--- a/subshell.rb",
+ "+++ b/subshell.rb",
+ "@@ -1,3 +1,2 @@",
+ "-`git status`",
+ "-`ls -la`",
+ " `ls -la`",
+ "+`git status`"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "957d2351752ecee0264d8b9cc4353348cbb52b75"
+ "shas": "611fa19dd10019ef47b3d7477c12855fe89177f2..8d03313c9be4bcd64a2a6a3c4047c5497a00686b"
}
,{
"testCaseDescription": "ruby-subshell-delete-test",
@@ -249,9 +295,17 @@
"filePaths": [
"subshell.rb"
],
- "sha1": "957d2351752ecee0264d8b9cc4353348cbb52b75",
+ "patch": [
+ "diff --git a/subshell.rb b/subshell.rb",
+ "index c695b4c..acb0008 100644",
+ "--- a/subshell.rb",
+ "+++ b/subshell.rb",
+ "@@ -1,2 +1 @@",
+ "-`ls -la`",
+ " `git status`"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "49e57b7abbf657b91d076a9f8b8e0d97f4becccc"
+ "shas": "8d03313c9be4bcd64a2a6a3c4047c5497a00686b..1b0cba06f36513f77bdbf325e75c866ed1311775"
}
,{
"testCaseDescription": "ruby-subshell-delete-rest-test",
@@ -280,7 +334,14 @@
"filePaths": [
"subshell.rb"
],
- "sha1": "49e57b7abbf657b91d076a9f8b8e0d97f4becccc",
+ "patch": [
+ "diff --git a/subshell.rb b/subshell.rb",
+ "index acb0008..e69de29 100644",
+ "--- a/subshell.rb",
+ "+++ b/subshell.rb",
+ "@@ -1 +0,0 @@",
+ "-`git status`"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "625fb3deaae6820d70e1d8cfe393b3d0c19484ff"
+ "shas": "1b0cba06f36513f77bdbf325e75c866ed1311775..bcd6d0b339d47a3a232e595d43db61acf2bfae04"
}]
diff --git a/test/corpus/diff-summaries/ruby/symbol.json b/test/corpus/diff-summaries/ruby/symbol.json
index b7724ff75..937380836 100644
--- a/test/corpus/diff-summaries/ruby/symbol.json
+++ b/test/corpus/diff-summaries/ruby/symbol.json
@@ -55,9 +55,18 @@
"filePaths": [
"symbol.rb"
],
- "sha1": "cf75d6b80230785d209c010331669dcc53f3131c",
+ "patch": [
+ "diff --git a/symbol.rb b/symbol.rb",
+ "index e69de29..faa7b3e 100644",
+ "--- a/symbol.rb",
+ "+++ b/symbol.rb",
+ "@@ -0,0 +1,3 @@",
+ "+:foo",
+ "+:'foo'",
+ "+:\"foo\""
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "145885fba74e95f43806a325975ef9f039cf136b"
+ "shas": "54b8896e3161e23f3cc38414d860e49c385d98ea..bf0c269b25a439dde0379686ee872b8ee1131636"
}
,{
"testCaseDescription": "ruby-symbol-replacement-insert-test",
@@ -161,9 +170,24 @@
"filePaths": [
"symbol.rb"
],
- "sha1": "145885fba74e95f43806a325975ef9f039cf136b",
+ "patch": [
+ "diff --git a/symbol.rb b/symbol.rb",
+ "index faa7b3e..c4e6184 100644",
+ "--- a/symbol.rb",
+ "+++ b/symbol.rb",
+ "@@ -1,3 +1,9 @@",
+ "+:bar",
+ "+:'bar'",
+ "+:\"bar\"",
+ "+:foo",
+ "+:'foo'",
+ "+:\"foo\"",
+ " :foo",
+ " :'foo'",
+ " :\"foo\""
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "c96b6788bd4c076d0672b6cba9b17ed6aa0feb6a"
+ "shas": "bf0c269b25a439dde0379686ee872b8ee1131636..5644f2ba2009c5ec36ecf85536876ede951bcf97"
}
,{
"testCaseDescription": "ruby-symbol-delete-insert-test",
@@ -258,9 +282,24 @@
"filePaths": [
"symbol.rb"
],
- "sha1": "c96b6788bd4c076d0672b6cba9b17ed6aa0feb6a",
+ "patch": [
+ "diff --git a/symbol.rb b/symbol.rb",
+ "index c4e6184..04cec42 100644",
+ "--- a/symbol.rb",
+ "+++ b/symbol.rb",
+ "@@ -1,6 +1,6 @@",
+ "-:bar",
+ "-:'bar'",
+ "-:\"bar\"",
+ "+:foo",
+ "+:'foo'",
+ "+:\"foo\"",
+ " :foo",
+ " :'foo'",
+ " :\"foo\""
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "dc360fda415247a5ed7935459301ea4c746af55a"
+ "shas": "5644f2ba2009c5ec36ecf85536876ede951bcf97..9c21efca119534d9cfc40651a91e427ea3d84754"
}
,{
"testCaseDescription": "ruby-symbol-replacement-test",
@@ -355,9 +394,24 @@
"filePaths": [
"symbol.rb"
],
- "sha1": "dc360fda415247a5ed7935459301ea4c746af55a",
+ "patch": [
+ "diff --git a/symbol.rb b/symbol.rb",
+ "index 04cec42..c4e6184 100644",
+ "--- a/symbol.rb",
+ "+++ b/symbol.rb",
+ "@@ -1,6 +1,6 @@",
+ "-:foo",
+ "-:'foo'",
+ "-:\"foo\"",
+ "+:bar",
+ "+:'bar'",
+ "+:\"bar\"",
+ " :foo",
+ " :'foo'",
+ " :\"foo\""
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e199efc80d424f729556605615ff031a24dc7e75"
+ "shas": "9c21efca119534d9cfc40651a91e427ea3d84754..610699faa6dc50b24bc691c72d95dd45a35d79ec"
}
,{
"testCaseDescription": "ruby-symbol-delete-replacement-test",
@@ -506,9 +560,27 @@
"filePaths": [
"symbol.rb"
],
- "sha1": "e199efc80d424f729556605615ff031a24dc7e75",
+ "patch": [
+ "diff --git a/symbol.rb b/symbol.rb",
+ "index c4e6184..977ce1c 100644",
+ "--- a/symbol.rb",
+ "+++ b/symbol.rb",
+ "@@ -1,9 +1,6 @@",
+ "-:bar",
+ "-:'bar'",
+ "-:\"bar\"",
+ "-:foo",
+ "-:'foo'",
+ "-:\"foo\"",
+ " :foo",
+ " :'foo'",
+ " :\"foo\"",
+ "+:bar",
+ "+:'bar'",
+ "+:\"bar\""
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "698896afb401223659dc997119289e912e8c6fd0"
+ "shas": "610699faa6dc50b24bc691c72d95dd45a35d79ec..7160921649a7890563e00272e08199d7d0b78bf4"
}
,{
"testCaseDescription": "ruby-symbol-delete-test",
@@ -567,9 +639,21 @@
"filePaths": [
"symbol.rb"
],
- "sha1": "698896afb401223659dc997119289e912e8c6fd0",
+ "patch": [
+ "diff --git a/symbol.rb b/symbol.rb",
+ "index 977ce1c..2109e60 100644",
+ "--- a/symbol.rb",
+ "+++ b/symbol.rb",
+ "@@ -1,6 +1,3 @@",
+ "-:foo",
+ "-:'foo'",
+ "-:\"foo\"",
+ " :bar",
+ " :'bar'",
+ " :\"bar\""
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "70736b33ee25ec327aa6a0a7fb94a40799e15163"
+ "shas": "7160921649a7890563e00272e08199d7d0b78bf4..5fba852ca0df591631002d4d49e810686949681b"
}
,{
"testCaseDescription": "ruby-symbol-delete-rest-test",
@@ -628,7 +712,16 @@
"filePaths": [
"symbol.rb"
],
- "sha1": "70736b33ee25ec327aa6a0a7fb94a40799e15163",
+ "patch": [
+ "diff --git a/symbol.rb b/symbol.rb",
+ "index 2109e60..e69de29 100644",
+ "--- a/symbol.rb",
+ "+++ b/symbol.rb",
+ "@@ -1,3 +0,0 @@",
+ "-:bar",
+ "-:'bar'",
+ "-:\"bar\""
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "1da7c8ba79becf9a9b091384779dc9bf9ab0136b"
+ "shas": "5fba852ca0df591631002d4d49e810686949681b..59e2edbe041b887605acb7a535fcceacb50d82a3"
}]
diff --git a/test/corpus/diff-summaries/ruby/ternary.json b/test/corpus/diff-summaries/ruby/ternary.json
index c99a75a62..21c4a79f4 100644
--- a/test/corpus/diff-summaries/ruby/ternary.json
+++ b/test/corpus/diff-summaries/ruby/ternary.json
@@ -12,11 +12,11 @@
],
"end": [
1,
- 26
+ 20
]
}
},
- "summary": "Added the 'condition' ternary expression"
+ "summary": "Added the 'foo' ternary expression"
}
]
},
@@ -25,9 +25,16 @@
"filePaths": [
"ternary.rb"
],
- "sha1": "c3ffed8011708e89709328349892066714996e97",
+ "patch": [
+ "diff --git a/ternary.rb b/ternary.rb",
+ "index e69de29..cc46e6d 100644",
+ "--- a/ternary.rb",
+ "+++ b/ternary.rb",
+ "@@ -0,0 +1 @@",
+ "+foo ? case1 : case2"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e2aa333c31548d7b47abc139eea8779a3148f2aa"
+ "shas": "97f870df43868da61ab367aca7fcbfdf8a77aa00..e1f849d81b2f0565744fbf4f45a7cf54b924eae8"
}
,{
"testCaseDescription": "ruby-ternary-replacement-insert-test",
@@ -36,30 +43,33 @@
"ternary.rb": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 26
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ }
},
- "summary": "Replaced the 'condition' ternary expression with the 'if condition then case 1 else case2\ncondition ? case1 : case2\ncondition ? case1 : case2\n' at line 1, column 1 - line 4, column 1"
+ "summary": "Added the 'bar' ternary expression"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ }
+ },
+ "summary": "Added the 'foo' ternary expression"
}
]
},
@@ -68,9 +78,18 @@
"filePaths": [
"ternary.rb"
],
- "sha1": "e2aa333c31548d7b47abc139eea8779a3148f2aa",
+ "patch": [
+ "diff --git a/ternary.rb b/ternary.rb",
+ "index cc46e6d..44ee69e 100644",
+ "--- a/ternary.rb",
+ "+++ b/ternary.rb",
+ "@@ -1 +1,3 @@",
+ "+bar ? a : b",
+ "+foo ? case1 : case2",
+ " foo ? case1 : case2"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "71869a05d963d2027782232660cbe032a43a963f"
+ "shas": "e1f849d81b2f0565744fbf4f45a7cf54b924eae8..15476ef40fd0d4fd9c8ae6157dc6039fbc450716"
}
,{
"testCaseDescription": "ruby-ternary-delete-insert-test",
@@ -86,8 +105,8 @@
1
],
"end": [
- 4,
- 1
+ 1,
+ 4
]
},
{
@@ -97,12 +116,66 @@
],
"end": [
1,
- 26
+ 4
]
}
]
},
- "summary": "Replaced the 'if condition then case 1 else case2\ncondition ? case1 : case2\ncondition ? case1 : case2\n' at line 1, column 1 - line 4, column 1 with the 'condition' ternary expression"
+ "summary": "Replaced the 'bar' identifier with the 'foo' identifier in the 'foo' ternary expression"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'a' identifier with the 'case1' identifier in the 'foo' ternary expression"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 11
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 15
+ ],
+ "end": [
+ 1,
+ 20
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'b' identifier with the 'case2' identifier in the 'foo' ternary expression"
}
]
},
@@ -111,9 +184,19 @@
"filePaths": [
"ternary.rb"
],
- "sha1": "71869a05d963d2027782232660cbe032a43a963f",
+ "patch": [
+ "diff --git a/ternary.rb b/ternary.rb",
+ "index 44ee69e..86614c8 100644",
+ "--- a/ternary.rb",
+ "+++ b/ternary.rb",
+ "@@ -1,3 +1,3 @@",
+ "-bar ? a : b",
+ "+foo ? case1 : case2",
+ " foo ? case1 : case2",
+ " foo ? case1 : case2"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "98f4f76d75b5b178b8962c8479483d404e2a5d59"
+ "shas": "15476ef40fd0d4fd9c8ae6157dc6039fbc450716..0f6207e02eb77f9f87e4a2b7256e0a80f978adc8"
}
,{
"testCaseDescription": "ruby-ternary-replacement-test",
@@ -130,7 +213,7 @@
],
"end": [
1,
- 26
+ 4
]
},
{
@@ -139,13 +222,67 @@
1
],
"end": [
- 4,
- 1
+ 1,
+ 4
]
}
]
},
- "summary": "Replaced the 'condition' ternary expression with the 'if condition then case 1 else case2\ncondition ? case1 : case2\ncondition ? case1 : case2\n' at line 1, column 1 - line 4, column 1"
+ "summary": "Replaced the 'foo' identifier with the 'bar' identifier in the 'bar' ternary expression"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'case1' identifier with the 'a' identifier in the 'bar' ternary expression"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 15
+ ],
+ "end": [
+ 1,
+ 20
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 11
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'case2' identifier with the 'b' identifier in the 'bar' ternary expression"
}
]
},
@@ -154,9 +291,19 @@
"filePaths": [
"ternary.rb"
],
- "sha1": "98f4f76d75b5b178b8962c8479483d404e2a5d59",
+ "patch": [
+ "diff --git a/ternary.rb b/ternary.rb",
+ "index 86614c8..44ee69e 100644",
+ "--- a/ternary.rb",
+ "+++ b/ternary.rb",
+ "@@ -1,3 +1,3 @@",
+ "-foo ? case1 : case2",
+ "+bar ? a : b",
+ " foo ? case1 : case2",
+ " foo ? case1 : case2"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "369b76639eb5496421b489e95f47304b0a022d58"
+ "shas": "0f6207e02eb77f9f87e4a2b7256e0a80f978adc8..1eb7b010282784002c1064e2433e57457e048cbb"
}
,{
"testCaseDescription": "ruby-ternary-delete-replacement-test",
@@ -165,30 +312,48 @@
"ternary.rb": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 26
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ }
},
- "summary": "Replaced the 'if condition then case 1 else case2\ncondition ? case1 : case2\ncondition ? case1 : case2\n' at line 1, column 1 - line 4, column 1 with the 'condition' ternary expression"
+ "summary": "Deleted the 'bar' ternary expression"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' ternary expression"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'bar' ternary expression"
}
]
},
@@ -197,9 +362,19 @@
"filePaths": [
"ternary.rb"
],
- "sha1": "369b76639eb5496421b489e95f47304b0a022d58",
+ "patch": [
+ "diff --git a/ternary.rb b/ternary.rb",
+ "index 44ee69e..1ce4e51 100644",
+ "--- a/ternary.rb",
+ "+++ b/ternary.rb",
+ "@@ -1,3 +1,2 @@",
+ "-bar ? a : b",
+ "-foo ? case1 : case2",
+ " foo ? case1 : case2",
+ "+bar ? a : b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "fe539acd7240395178acb21418efe1c1ae1ffb95"
+ "shas": "1eb7b010282784002c1064e2433e57457e048cbb..16fba8824d7b308daeae80ae16375ff007846b9b"
}
,{
"testCaseDescription": "ruby-ternary-delete-test",
@@ -215,11 +390,11 @@
],
"end": [
1,
- 26
+ 20
]
}
},
- "summary": "Deleted the 'condition' ternary expression"
+ "summary": "Deleted the 'foo' ternary expression"
}
]
},
@@ -228,15 +403,22 @@
"filePaths": [
"ternary.rb"
],
- "sha1": "fe539acd7240395178acb21418efe1c1ae1ffb95",
+ "patch": [
+ "diff --git a/ternary.rb b/ternary.rb",
+ "index 1ce4e51..7f42328 100644",
+ "--- a/ternary.rb",
+ "+++ b/ternary.rb",
+ "@@ -1,2 +1 @@",
+ "-foo ? case1 : case2",
+ " bar ? a : b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e4ee68c328041f87bcd3c08fa24eeeae9d08e173"
+ "shas": "16fba8824d7b308daeae80ae16375ff007846b9b..0783eee8d94a9d7a8f7d590f0a9716617e145336"
}
,{
"testCaseDescription": "ruby-ternary-delete-rest-test",
"expectedResult": {
- "changes": {},
- "errors": {
+ "changes": {
"ternary.rb": [
{
"span": {
@@ -246,20 +428,28 @@
1
],
"end": [
- 2,
- 1
+ 1,
+ 12
]
}
},
- "summary": "Deleted the 'if condition then case 1 else case2\n' at line 1, column 1 - line 2, column 1"
+ "summary": "Deleted the 'bar' ternary expression"
}
]
- }
+ },
+ "errors": {}
},
"filePaths": [
"ternary.rb"
],
- "sha1": "e4ee68c328041f87bcd3c08fa24eeeae9d08e173",
+ "patch": [
+ "diff --git a/ternary.rb b/ternary.rb",
+ "index 7f42328..e69de29 100644",
+ "--- a/ternary.rb",
+ "+++ b/ternary.rb",
+ "@@ -1 +0,0 @@",
+ "-bar ? a : b"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "1d64a73244315b920d5fe90966068c5c81009362"
+ "shas": "0783eee8d94a9d7a8f7d590f0a9716617e145336..ec2870c9e829ba9514a3fc196f778f73f25ff514"
}]
diff --git a/test/corpus/diff-summaries/ruby/unless.json b/test/corpus/diff-summaries/ruby/unless.json
index 3d56ae002..5ecb0f9ca 100644
--- a/test/corpus/diff-summaries/ruby/unless.json
+++ b/test/corpus/diff-summaries/ruby/unless.json
@@ -25,9 +25,20 @@
"filePaths": [
"unless.rb"
],
- "sha1": "482d92220765ab9cc71c4a13b264d98554a987b2",
+ "patch": [
+ "diff --git a/unless.rb b/unless.rb",
+ "index e69de29..dd4d758 100644",
+ "--- a/unless.rb",
+ "+++ b/unless.rb",
+ "@@ -0,0 +1,5 @@",
+ "+unless foo",
+ "+ bar",
+ "+else",
+ "+ bat",
+ "+end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e57f0f844cb0070e411b752d1191a6f29a68cca4"
+ "shas": "eb51a430951de620d64e6e92df9603e953708321..3305c9604e19f1adb5acc1ac48128f02ba8824b5"
}
,{
"testCaseDescription": "ruby-unless-replacement-insert-test",
@@ -86,9 +97,27 @@
"filePaths": [
"unless.rb"
],
- "sha1": "e57f0f844cb0070e411b752d1191a6f29a68cca4",
+ "patch": [
+ "diff --git a/unless.rb b/unless.rb",
+ "index dd4d758..6e36f98 100644",
+ "--- a/unless.rb",
+ "+++ b/unless.rb",
+ "@@ -1,3 +1,12 @@",
+ "+unless x",
+ "+end",
+ "+unless y then",
+ "+end",
+ "+unless foo",
+ "+ bar",
+ "+else",
+ "+ bat",
+ "+end",
+ " unless foo",
+ " bar",
+ " else"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "08f3e10b268b224faaa60849cefdb2e89c84194b"
+ "shas": "3305c9604e19f1adb5acc1ac48128f02ba8824b5..b375e5596a5e365eafe9b0d2bec7778f71f80a59"
}
,{
"testCaseDescription": "ruby-unless-delete-insert-test",
@@ -120,34 +149,22 @@
}
]
},
- "summary": "Replaced the 'x' identifier with the 'foo' identifier"
+ "summary": "Replaced the 'x' identifier with the 'foo' identifier in the foo unless statement"
},
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 9
- ],
- "end": [
- 2,
- 1
- ]
- },
- {
- "start": [
- 2,
- 3
- ],
- "end": [
- 2,
- 6
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
},
- "summary": "Replaced the '\n' expression statements with the 'bar' identifier"
+ "summary": "Added the 'bar' identifier in the foo unless statement"
},
{
"span": {
@@ -162,7 +179,7 @@
]
}
},
- "summary": "Added the 'bat' identifier"
+ "summary": "Added the 'bat' identifier in the foo unless statement"
},
{
"span": {
@@ -186,9 +203,25 @@
"filePaths": [
"unless.rb"
],
- "sha1": "08f3e10b268b224faaa60849cefdb2e89c84194b",
+ "patch": [
+ "diff --git a/unless.rb b/unless.rb",
+ "index 6e36f98..39ae1f8 100644",
+ "--- a/unless.rb",
+ "+++ b/unless.rb",
+ "@@ -1,6 +1,7 @@",
+ "-unless x",
+ "-end",
+ "-unless y then",
+ "+unless foo",
+ "+ bar",
+ "+else",
+ "+ bat",
+ " end",
+ " unless foo",
+ " bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e5d47434dc9c9fdeaa32aed4642c49f4afd48ebc"
+ "shas": "b375e5596a5e365eafe9b0d2bec7778f71f80a59..f8fdadec2dc18f26cceabd013cc59cfc925f261d"
}
,{
"testCaseDescription": "ruby-unless-replacement-test",
@@ -220,34 +253,22 @@
}
]
},
- "summary": "Replaced the 'foo' identifier with the 'x' identifier"
+ "summary": "Replaced the 'foo' identifier with the 'x' identifier in the x unless statement"
},
{
"span": {
- "replace": [
- {
- "start": [
- 2,
- 3
- ],
- "end": [
- 2,
- 6
- ]
- },
- {
- "start": [
- 1,
- 9
- ],
- "end": [
- 2,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
},
- "summary": "Replaced the 'bar' identifier with the '\n' expression statements"
+ "summary": "Deleted the 'bar' identifier in the x unless statement"
},
{
"span": {
@@ -262,7 +283,7 @@
]
}
},
- "summary": "Deleted the 'bat' identifier"
+ "summary": "Deleted the 'bat' identifier in the x unless statement"
},
{
"span": {
@@ -286,9 +307,25 @@
"filePaths": [
"unless.rb"
],
- "sha1": "e5d47434dc9c9fdeaa32aed4642c49f4afd48ebc",
+ "patch": [
+ "diff --git a/unless.rb b/unless.rb",
+ "index 39ae1f8..6e36f98 100644",
+ "--- a/unless.rb",
+ "+++ b/unless.rb",
+ "@@ -1,7 +1,6 @@",
+ "-unless foo",
+ "- bar",
+ "-else",
+ "- bat",
+ "+unless x",
+ "+end",
+ "+unless y then",
+ " end",
+ " unless foo",
+ " bar"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "6ef7542dbcbd76333dbe0774882c27122223ce5f"
+ "shas": "f8fdadec2dc18f26cceabd013cc59cfc925f261d..ed0a3d5a27a0fef38499b6b79183b9afe9898a0e"
}
,{
"testCaseDescription": "ruby-unless-delete-replacement-test",
@@ -317,9 +354,32 @@
"filePaths": [
"unless.rb"
],
- "sha1": "6ef7542dbcbd76333dbe0774882c27122223ce5f",
+ "patch": [
+ "diff --git a/unless.rb b/unless.rb",
+ "index 6e36f98..5efe10d 100644",
+ "--- a/unless.rb",
+ "+++ b/unless.rb",
+ "@@ -1,14 +1,9 @@",
+ "-unless x",
+ "-end",
+ "-unless y then",
+ "-end",
+ " unless foo",
+ " bar",
+ " else",
+ " bat",
+ " end",
+ "-unless foo",
+ "- bar",
+ "-else",
+ "- bat",
+ "+unless x",
+ "+end",
+ "+unless y then",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "57de04c95aecdc72ceb03568e0fdb3d74cf376ff"
+ "shas": "ed0a3d5a27a0fef38499b6b79183b9afe9898a0e..0a0941c08b3a3f65dbcbf32e375689ae3c541b42"
}
,{
"testCaseDescription": "ruby-unless-delete-test",
@@ -348,9 +408,23 @@
"filePaths": [
"unless.rb"
],
- "sha1": "57de04c95aecdc72ceb03568e0fdb3d74cf376ff",
+ "patch": [
+ "diff --git a/unless.rb b/unless.rb",
+ "index 5efe10d..a38714d 100644",
+ "--- a/unless.rb",
+ "+++ b/unless.rb",
+ "@@ -1,8 +1,3 @@",
+ "-unless foo",
+ "- bar",
+ "-else",
+ "- bat",
+ "-end",
+ " unless x",
+ " end",
+ " unless y then"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "3689a75b98efc2b8de2658d0f6eb29f0015b3828"
+ "shas": "0a0941c08b3a3f65dbcbf32e375689ae3c541b42..95eeab305a4bd6687a1e532bc9be0965422ba737"
}
,{
"testCaseDescription": "ruby-unless-delete-rest-test",
@@ -394,7 +468,17 @@
"filePaths": [
"unless.rb"
],
- "sha1": "3689a75b98efc2b8de2658d0f6eb29f0015b3828",
+ "patch": [
+ "diff --git a/unless.rb b/unless.rb",
+ "index a38714d..e69de29 100644",
+ "--- a/unless.rb",
+ "+++ b/unless.rb",
+ "@@ -1,4 +0,0 @@",
+ "-unless x",
+ "-end",
+ "-unless y then",
+ "-end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "9dee69155ea3541370dce7da3a81e7d3940e2317"
+ "shas": "95eeab305a4bd6687a1e532bc9be0965422ba737..4bf7d0bf7a5f56e68acbec672e139df1702a7f37"
}]
diff --git a/test/corpus/diff-summaries/ruby/until.json b/test/corpus/diff-summaries/ruby/until.json
index 3dcdb46c3..409e5be11 100644
--- a/test/corpus/diff-summaries/ruby/until.json
+++ b/test/corpus/diff-summaries/ruby/until.json
@@ -40,9 +40,18 @@
"filePaths": [
"until.rb"
],
- "sha1": "afb10073d68a4e2f0fbaac9a77f612de65bbccbe",
+ "patch": [
+ "diff --git a/until.rb b/until.rb",
+ "index e69de29..2785b0d 100644",
+ "--- a/until.rb",
+ "+++ b/until.rb",
+ "@@ -0,0 +1,3 @@",
+ "+until foo do",
+ "+end",
+ "+foo until done"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "6780e35bdc5913d3fc7f4ae577adb8b4fdc3b194"
+ "shas": "527524ae442ea64d2a0f8d057a8f3f29091b94b7..7195bbfd7970acfb3f61a3a04144c6ed735d95f8"
}
,{
"testCaseDescription": "ruby-until-replacement-insert-test",
@@ -101,9 +110,24 @@
"filePaths": [
"until.rb"
],
- "sha1": "6780e35bdc5913d3fc7f4ae577adb8b4fdc3b194",
+ "patch": [
+ "diff --git a/until.rb b/until.rb",
+ "index 2785b0d..7c5868e 100644",
+ "--- a/until.rb",
+ "+++ b/until.rb",
+ "@@ -1,3 +1,9 @@",
+ "+until foo",
+ "+ bar",
+ "+end",
+ "+until foo do",
+ "+end",
+ "+foo until done",
+ " until foo do",
+ " end",
+ " foo until done"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "0df6b2c10e983b7f0f24922996a0ea94ddb22619"
+ "shas": "7195bbfd7970acfb3f61a3a04144c6ed735d95f8..a9c0d66a0ce29c04ddfdb3eeb9fd5133df7ad7c4"
}
,{
"testCaseDescription": "ruby-until-delete-insert-test",
@@ -147,9 +171,23 @@
"filePaths": [
"until.rb"
],
- "sha1": "0df6b2c10e983b7f0f24922996a0ea94ddb22619",
+ "patch": [
+ "diff --git a/until.rb b/until.rb",
+ "index 7c5868e..c51b0d0 100644",
+ "--- a/until.rb",
+ "+++ b/until.rb",
+ "@@ -1,6 +1,6 @@",
+ "-until foo",
+ "- bar",
+ "+until foo do",
+ " end",
+ "+foo until done",
+ " until foo do",
+ " end",
+ " foo until done"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "c191ed363b003098cef1ca46778033443fcee4bd"
+ "shas": "a9c0d66a0ce29c04ddfdb3eeb9fd5133df7ad7c4..5e66fb4320749066c271c6ee5922a6662f0f66fc"
}
,{
"testCaseDescription": "ruby-until-replacement-test",
@@ -193,9 +231,23 @@
"filePaths": [
"until.rb"
],
- "sha1": "c191ed363b003098cef1ca46778033443fcee4bd",
+ "patch": [
+ "diff --git a/until.rb b/until.rb",
+ "index c51b0d0..7c5868e 100644",
+ "--- a/until.rb",
+ "+++ b/until.rb",
+ "@@ -1,6 +1,6 @@",
+ "-until foo do",
+ "+until foo",
+ "+ bar",
+ " end",
+ "-foo until done",
+ " until foo do",
+ " end",
+ " foo until done"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "f0c1239d16c2628f928ac58736c95992a2f10923"
+ "shas": "5e66fb4320749066c271c6ee5922a6662f0f66fc..aee5892096fa1235af544e9f239aea971a299847"
}
,{
"testCaseDescription": "ruby-until-delete-replacement-test",
@@ -269,9 +321,26 @@
"filePaths": [
"until.rb"
],
- "sha1": "f0c1239d16c2628f928ac58736c95992a2f10923",
+ "patch": [
+ "diff --git a/until.rb b/until.rb",
+ "index 7c5868e..c543483 100644",
+ "--- a/until.rb",
+ "+++ b/until.rb",
+ "@@ -1,9 +1,6 @@",
+ "-until foo",
+ "- bar",
+ "-end",
+ " until foo do",
+ " end",
+ " foo until done",
+ "-until foo do",
+ "+until foo",
+ "+ bar",
+ " end",
+ "-foo until done"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "94c63611ca1981024d1113d68f6cc4476d3b2715"
+ "shas": "aee5892096fa1235af544e9f239aea971a299847..9fc09b78cdd42bc642860cebd38a3d5baff394b4"
}
,{
"testCaseDescription": "ruby-until-delete-test",
@@ -315,9 +384,21 @@
"filePaths": [
"until.rb"
],
- "sha1": "94c63611ca1981024d1113d68f6cc4476d3b2715",
+ "patch": [
+ "diff --git a/until.rb b/until.rb",
+ "index c543483..347b5ff 100644",
+ "--- a/until.rb",
+ "+++ b/until.rb",
+ "@@ -1,6 +1,3 @@",
+ "-until foo do",
+ "-end",
+ "-foo until done",
+ " until foo",
+ " bar",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "a0540b9451554f2a624c6562070f7df8115dfefe"
+ "shas": "9fc09b78cdd42bc642860cebd38a3d5baff394b4..f878f5c2c585d3cab149cd4d3402426421383914"
}
,{
"testCaseDescription": "ruby-until-delete-rest-test",
@@ -346,7 +427,16 @@
"filePaths": [
"until.rb"
],
- "sha1": "a0540b9451554f2a624c6562070f7df8115dfefe",
+ "patch": [
+ "diff --git a/until.rb b/until.rb",
+ "index 347b5ff..e69de29 100644",
+ "--- a/until.rb",
+ "+++ b/until.rb",
+ "@@ -1,3 +0,0 @@",
+ "-until foo",
+ "- bar",
+ "-end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "03b2db1cb47a50501b36faf7fc35ebd3347c0a0a"
+ "shas": "f878f5c2c585d3cab149cd4d3402426421383914..9a18b4c80b2e7e2bdca5da3ea6388d1cb4727f8f"
}]
diff --git a/test/corpus/diff-summaries/ruby/when-else.json b/test/corpus/diff-summaries/ruby/when-else.json
new file mode 100644
index 000000000..616eeee56
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/when-else.json
@@ -0,0 +1,274 @@
+[{
+ "testCaseDescription": "ruby-when-else-setup-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index e69de29..3c8eff2 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -0,0 +1,4 @@",
+ "+case foo",
+ "+when bar",
+ "+ baz",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "4bf7d0bf7a5f56e68acbec672e139df1702a7f37..5b4964a35255ff016d9da31b9cb8bf36778aa043"
+}
+,{
+ "testCaseDescription": "ruby-when-else-insert-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Added an else block in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index 3c8eff2..fb2be92 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -1,4 +1,5 @@",
+ " case foo",
+ " when bar",
+ " baz",
+ "+else",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "5b4964a35255ff016d9da31b9cb8bf36778aa043..bc90856b69058e9fbce171c0c94504ce05b21a75"
+}
+,{
+ "testCaseDescription": "ruby-when-else-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ },
+ {
+ "start": [
+ 5,
+ 3
+ ],
+ "end": [
+ 5,
+ 6
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced an else block with an 'qoz' identifier in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index fb2be92..028bb59 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -2,4 +2,5 @@ case foo",
+ " when bar",
+ " baz",
+ " else",
+ "+ qoz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "bc90856b69058e9fbce171c0c94504ce05b21a75..44f9ec6f04b1705e4fcc65bd704593c6945d7f77"
+}
+,{
+ "testCaseDescription": "ruby-when-else-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 5,
+ 3
+ ],
+ "end": [
+ 5,
+ 6
+ ]
+ },
+ {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'qoz' identifier with the else block in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index 028bb59..fb2be92 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -2,5 +2,4 @@ case foo",
+ " when bar",
+ " baz",
+ " else",
+ "- qoz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "44f9ec6f04b1705e4fcc65bd704593c6945d7f77..c1b522289f7864ca47e536478df06830c958061d"
+}
+,{
+ "testCaseDescription": "ruby-when-else-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted an else block in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index fb2be92..3c8eff2 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -1,5 +1,4 @@",
+ " case foo",
+ " when bar",
+ " baz",
+ "-else",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c1b522289f7864ca47e536478df06830c958061d..c3668122d9d5da3171cf5e831a48ee3f42cdb19e"
+}
+,{
+ "testCaseDescription": "ruby-when-else-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index 3c8eff2..e69de29 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -1,4 +0,0 @@",
+ "-case foo",
+ "-when bar",
+ "- baz",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c3668122d9d5da3171cf5e831a48ee3f42cdb19e..51729c359e350d71395532126c23bfed960f2373"
+}]
diff --git a/test/corpus/diff-summaries/ruby/when.json b/test/corpus/diff-summaries/ruby/when.json
new file mode 100644
index 000000000..5178efb68
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/when.json
@@ -0,0 +1,240 @@
+[{
+ "testCaseDescription": "ruby-when-setup-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index e69de29..ee23477 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -0,0 +1,2 @@",
+ "+case foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "dc9d24ac927d2ba1f4d7331d5edcf9888c6bfbdf..8584062d9a54a14c1af0ac949bf9be286269f7f7"
+}
+,{
+ "testCaseDescription": "ruby-when-insert-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 3,
+ 1
+ ]
+ }
+ },
+ "summary": "Added the 'bar' when comparison in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index ee23477..92a40ca 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -1,2 +1,3 @@",
+ " case foo",
+ "+when bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "8584062d9a54a14c1af0ac949bf9be286269f7f7..522104f5e945e8b8529bcf56c273953d72594afa"
+}
+,{
+ "testCaseDescription": "ruby-when-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'baz' identifier in a when comparison"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index 92a40ca..3c8eff2 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -1,3 +1,4 @@",
+ " case foo",
+ " when bar",
+ "+ baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "522104f5e945e8b8529bcf56c273953d72594afa..c35811be8fcc9afe2fad9fd988d9e95189c58765"
+}
+,{
+ "testCaseDescription": "ruby-when-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'baz' identifier in a when comparison"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index 3c8eff2..92a40ca 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -1,4 +1,3 @@",
+ " case foo",
+ " when bar",
+ "- baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c35811be8fcc9afe2fad9fd988d9e95189c58765..d091c742bdff6528f0464c6a0e1d369f6060ed1d"
+}
+,{
+ "testCaseDescription": "ruby-when-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 3,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' when comparison in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index 92a40ca..ee23477 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -1,3 +1,2 @@",
+ " case foo",
+ "-when bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d091c742bdff6528f0464c6a0e1d369f6060ed1d..0d554900e6183bbfd1dc9ed4b90ffb74901991d6"
+}
+,{
+ "testCaseDescription": "ruby-when-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index ee23477..e69de29 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -1,2 +0,0 @@",
+ "-case foo",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "0d554900e6183bbfd1dc9ed4b90ffb74901991d6..c723ad6d1865bc31b8b6d554c0768635937c0ab3"
+}]
diff --git a/test/corpus/diff-summaries/ruby/while.json b/test/corpus/diff-summaries/ruby/while.json
index df9240e0d..8669b93ec 100644
--- a/test/corpus/diff-summaries/ruby/while.json
+++ b/test/corpus/diff-summaries/ruby/while.json
@@ -40,9 +40,18 @@
"filePaths": [
"while.rb"
],
- "sha1": "1cda9292af04e8e32459e7947db6705129af8474",
+ "patch": [
+ "diff --git a/while.rb b/while.rb",
+ "index e69de29..9990bdf 100644",
+ "--- a/while.rb",
+ "+++ b/while.rb",
+ "@@ -0,0 +1,3 @@",
+ "+while foo do",
+ "+end",
+ "+foo while run"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "ccc0f8b7ebdbea4583be97bde9e61f8347ffa7a7"
+ "shas": "0ea1cbaad545a54267144f11a8d792fca30cf547..1c849fa3191de04f500a9534aae7f04708bae91e"
}
,{
"testCaseDescription": "ruby-while-replacement-insert-test",
@@ -101,9 +110,24 @@
"filePaths": [
"while.rb"
],
- "sha1": "ccc0f8b7ebdbea4583be97bde9e61f8347ffa7a7",
+ "patch": [
+ "diff --git a/while.rb b/while.rb",
+ "index 9990bdf..5a24260 100644",
+ "--- a/while.rb",
+ "+++ b/while.rb",
+ "@@ -1,3 +1,9 @@",
+ "+while foo",
+ "+ bar",
+ "+end",
+ "+while foo do",
+ "+end",
+ "+foo while run",
+ " while foo do",
+ " end",
+ " foo while run"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "46a3d9d718783adb324062310e31c22b4ea99d1d"
+ "shas": "1c849fa3191de04f500a9534aae7f04708bae91e..ce45201d611ff1a381bee7c0d7b4eba2a5261228"
}
,{
"testCaseDescription": "ruby-while-delete-insert-test",
@@ -147,9 +171,23 @@
"filePaths": [
"while.rb"
],
- "sha1": "46a3d9d718783adb324062310e31c22b4ea99d1d",
+ "patch": [
+ "diff --git a/while.rb b/while.rb",
+ "index 5a24260..c0c26cd 100644",
+ "--- a/while.rb",
+ "+++ b/while.rb",
+ "@@ -1,6 +1,6 @@",
+ "-while foo",
+ "- bar",
+ "+while foo do",
+ " end",
+ "+foo while run",
+ " while foo do",
+ " end",
+ " foo while run"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "cc57d6e60dbcb0ae0d8ec140fcbbf78a88db5664"
+ "shas": "ce45201d611ff1a381bee7c0d7b4eba2a5261228..76f1616d8999184e0058a66f6871ca4f039f5e1c"
}
,{
"testCaseDescription": "ruby-while-replacement-test",
@@ -193,9 +231,23 @@
"filePaths": [
"while.rb"
],
- "sha1": "cc57d6e60dbcb0ae0d8ec140fcbbf78a88db5664",
+ "patch": [
+ "diff --git a/while.rb b/while.rb",
+ "index c0c26cd..5a24260 100644",
+ "--- a/while.rb",
+ "+++ b/while.rb",
+ "@@ -1,6 +1,6 @@",
+ "-while foo do",
+ "+while foo",
+ "+ bar",
+ " end",
+ "-foo while run",
+ " while foo do",
+ " end",
+ " foo while run"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "36e72337e431c5aa034e91f9112fbe8d83e229be"
+ "shas": "76f1616d8999184e0058a66f6871ca4f039f5e1c..d2fb5c6486f918b1d250f5561389fec71fadc005"
}
,{
"testCaseDescription": "ruby-while-delete-replacement-test",
@@ -269,9 +321,26 @@
"filePaths": [
"while.rb"
],
- "sha1": "36e72337e431c5aa034e91f9112fbe8d83e229be",
+ "patch": [
+ "diff --git a/while.rb b/while.rb",
+ "index 5a24260..3763a72 100644",
+ "--- a/while.rb",
+ "+++ b/while.rb",
+ "@@ -1,9 +1,6 @@",
+ "-while foo",
+ "- bar",
+ "-end",
+ " while foo do",
+ " end",
+ " foo while run",
+ "-while foo do",
+ "+while foo",
+ "+ bar",
+ " end",
+ "-foo while run"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "c99322df426c012caff854061c30f59fd2ca36a3"
+ "shas": "d2fb5c6486f918b1d250f5561389fec71fadc005..deb693d7595e21ca8bf5d127aba20362b01259ee"
}
,{
"testCaseDescription": "ruby-while-delete-test",
@@ -315,9 +384,21 @@
"filePaths": [
"while.rb"
],
- "sha1": "c99322df426c012caff854061c30f59fd2ca36a3",
+ "patch": [
+ "diff --git a/while.rb b/while.rb",
+ "index 3763a72..57e673b 100644",
+ "--- a/while.rb",
+ "+++ b/while.rb",
+ "@@ -1,6 +1,3 @@",
+ "-while foo do",
+ "-end",
+ "-foo while run",
+ " while foo",
+ " bar",
+ " end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "680f1e37086073733a197ae27258b428cc7eb643"
+ "shas": "deb693d7595e21ca8bf5d127aba20362b01259ee..b96838d1e529db101b960f04c66dd54aeec21d92"
}
,{
"testCaseDescription": "ruby-while-delete-rest-test",
@@ -346,7 +427,16 @@
"filePaths": [
"while.rb"
],
- "sha1": "680f1e37086073733a197ae27258b428cc7eb643",
+ "patch": [
+ "diff --git a/while.rb b/while.rb",
+ "index 57e673b..e69de29 100644",
+ "--- a/while.rb",
+ "+++ b/while.rb",
+ "@@ -1,3 +0,0 @@",
+ "-while foo",
+ "- bar",
+ "-end"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "afb10073d68a4e2f0fbaac9a77f612de65bbccbe"
+ "shas": "b96838d1e529db101b960f04c66dd54aeec21d92..527524ae442ea64d2a0f8d057a8f3f29091b94b7"
}]
diff --git a/test/corpus/diff-summaries/ruby/yield.json b/test/corpus/diff-summaries/ruby/yield.json
index 86a9ca415..2fbd99c84 100644
--- a/test/corpus/diff-summaries/ruby/yield.json
+++ b/test/corpus/diff-summaries/ruby/yield.json
@@ -25,9 +25,16 @@
"filePaths": [
"yield.rb"
],
- "sha1": "9b31b02e831a9ab3366e95bcb9f6399451d97d76",
+ "patch": [
+ "diff --git a/yield.rb b/yield.rb",
+ "index e69de29..a1e1b84 100644",
+ "--- a/yield.rb",
+ "+++ b/yield.rb",
+ "@@ -0,0 +1 @@",
+ "+yield foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "dbee6f357338aaa3f39b672e6b1b4523a8f04484"
+ "shas": "e9e47a7e8dfaea6fade11176891263b27322f29d..d3c71a8b9429b7706728aaf0e2ab22580c5a7409"
}
,{
"testCaseDescription": "ruby-yield-replacement-insert-test",
@@ -71,9 +78,18 @@
"filePaths": [
"yield.rb"
],
- "sha1": "dbee6f357338aaa3f39b672e6b1b4523a8f04484",
+ "patch": [
+ "diff --git a/yield.rb b/yield.rb",
+ "index a1e1b84..2f5c2c5 100644",
+ "--- a/yield.rb",
+ "+++ b/yield.rb",
+ "@@ -1 +1,3 @@",
+ "+yield",
+ "+yield foo",
+ " yield foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "e67fd93b9125fcde8c8409b783b4655c06a3df25"
+ "shas": "d3c71a8b9429b7706728aaf0e2ab22580c5a7409..72ab3af267ac70da88be18c80d66436faa4d4631"
}
,{
"testCaseDescription": "ruby-yield-delete-insert-test",
@@ -102,9 +118,19 @@
"filePaths": [
"yield.rb"
],
- "sha1": "e67fd93b9125fcde8c8409b783b4655c06a3df25",
+ "patch": [
+ "diff --git a/yield.rb b/yield.rb",
+ "index 2f5c2c5..8e68f90 100644",
+ "--- a/yield.rb",
+ "+++ b/yield.rb",
+ "@@ -1,3 +1,3 @@",
+ "-yield",
+ "+yield foo",
+ " yield foo",
+ " yield foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "2141d5505436e89dfb53f08627a0763751731a5f"
+ "shas": "72ab3af267ac70da88be18c80d66436faa4d4631..b4c41867bc41e284d0edc33e675ee3717fb1d913"
}
,{
"testCaseDescription": "ruby-yield-replacement-test",
@@ -133,9 +159,19 @@
"filePaths": [
"yield.rb"
],
- "sha1": "2141d5505436e89dfb53f08627a0763751731a5f",
+ "patch": [
+ "diff --git a/yield.rb b/yield.rb",
+ "index 8e68f90..2f5c2c5 100644",
+ "--- a/yield.rb",
+ "+++ b/yield.rb",
+ "@@ -1,3 +1,3 @@",
+ "-yield foo",
+ "+yield",
+ " yield foo",
+ " yield foo"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "275211816068d07474e95acca8a51626e2c2bf9c"
+ "shas": "b4c41867bc41e284d0edc33e675ee3717fb1d913..45587e828108c8da4b0ed81e4e9eba811537864c"
}
,{
"testCaseDescription": "ruby-yield-delete-replacement-test",
@@ -194,9 +230,19 @@
"filePaths": [
"yield.rb"
],
- "sha1": "275211816068d07474e95acca8a51626e2c2bf9c",
+ "patch": [
+ "diff --git a/yield.rb b/yield.rb",
+ "index 2f5c2c5..324b0fe 100644",
+ "--- a/yield.rb",
+ "+++ b/yield.rb",
+ "@@ -1,3 +1,2 @@",
+ "-yield",
+ "-yield foo",
+ " yield foo",
+ "+yield"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "904f13395ebdcccb186a779f0a06b94811fdebe0"
+ "shas": "45587e828108c8da4b0ed81e4e9eba811537864c..2174ca8275e9a78b58f66ad3b64a5cae11f83be0"
}
,{
"testCaseDescription": "ruby-yield-delete-test",
@@ -225,9 +271,17 @@
"filePaths": [
"yield.rb"
],
- "sha1": "904f13395ebdcccb186a779f0a06b94811fdebe0",
+ "patch": [
+ "diff --git a/yield.rb b/yield.rb",
+ "index 324b0fe..fcd1a85 100644",
+ "--- a/yield.rb",
+ "+++ b/yield.rb",
+ "@@ -1,2 +1 @@",
+ "-yield foo",
+ " yield"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "abe626de0237f33d3420253ca7569dace23da8ae"
+ "shas": "2174ca8275e9a78b58f66ad3b64a5cae11f83be0..ded54423d631ab67007dd284c87a8628935009ce"
}
,{
"testCaseDescription": "ruby-yield-delete-rest-test",
@@ -256,7 +310,14 @@
"filePaths": [
"yield.rb"
],
- "sha1": "abe626de0237f33d3420253ca7569dace23da8ae",
+ "patch": [
+ "diff --git a/yield.rb b/yield.rb",
+ "index fcd1a85..e69de29 100644",
+ "--- a/yield.rb",
+ "+++ b/yield.rb",
+ "@@ -1 +0,0 @@",
+ "-yield"
+ ],
"gitDir": "test/corpus/repos/ruby",
- "sha2": "1cda9292af04e8e32459e7947db6705129af8474"
+ "shas": "ded54423d631ab67007dd284c87a8628935009ce..0ea1cbaad545a54267144f11a8d792fca30cf547"
}]
diff --git a/test/corpus/generated/new_ruby.json b/test/corpus/generated/new_ruby.json
new file mode 100644
index 000000000..9305a903c
--- /dev/null
+++ b/test/corpus/generated/new_ruby.json
@@ -0,0 +1,14 @@
+[
+ {
+ "language": "ruby",
+ "fileExt": ".rb",
+ "repoUrl": "https://github.com/diff-fixtures/ruby.git",
+ "syntaxes": [
+ {
+ "syntax": "module",
+ "insert": "module Foo\nend",
+ "replacement": "module Foo\n def bar\n end\nend"
+ }
+ ]
+ }
+]
diff --git a/test/corpus/generated/ruby.json b/test/corpus/generated/ruby.json
index 058a5438d..a908d02a4 100644
--- a/test/corpus/generated/ruby.json
+++ b/test/corpus/generated/ruby.json
@@ -7,192 +7,260 @@
{
"syntax": "assignment",
"insert": "x = 0",
- "replacement": "x = 1",
+ "replacement": "x = 1"
},
{
"syntax": "comment",
"insert": "# This is a comment",
- "replacement": "=begin\nThis is a multiline\ncomment\n=end",
+ "replacement": "=begin\nThis is a multiline\ncomment\n=end"
},
{
"syntax": "number",
"insert": "1234\n1_234\n0d1_234\n0xa_bcd_ef0_123_456_789\n0o1234567\n0b1_0\n1.234_5e678_90\n",
- "replacement": "1235\n1_235\n0d1_235\n0xa_bcd_ef0_123_456_788\n0o1234576\n0b1_1\n1.234_5e678_91\n",
+ "replacement": "1235\n1_235\n0d1_235\n0xa_bcd_ef0_123_456_788\n0o1234576\n0b1_1\n1.234_5e678_91\n"
},
{
"syntax": "symbol",
"insert": ":foo\n:'foo'\n:\"foo\"",
- "replacement": ":bar\n:'bar'\n:\"bar\"",
+ "replacement": ":bar\n:'bar'\n:\"bar\""
},
{
"syntax": "string",
"insert": "''\n'foo with \"bar\"'",
- "replacement": "\"\"\n\"bar with 'foo'\"",
+ "replacement": "\"\"\n\"bar with 'foo'\""
},
{
"syntax": "interpolation",
"insert": ":\"foo #{bar}\"\n\"foo #{bar}\"",
- "replacement": ":\"bar #{foo}\"\n\"bar #{foo}\"",
+ "replacement": ":\"bar #{foo}\"\n\"bar #{foo}\""
},
{
"syntax": "delimiter",
"insert": "%q#a#\n%qc>\n%#a#\n%Q#a#\n%c>\n%Qc>",
- "replacement": "%q/b/\n%q{d{e}f}\n%/b/\n%Q/b/\n%{d{e}f}\n%Q{d{e}f}",
+ "replacement": "%q/b/\n%q{d{e}f}\n%/b/\n%Q/b/\n%{d{e}f}\n%Q{d{e}f}"
},
{
"syntax": "math-assignment",
"insert": "x += 1\nx -= 1\nx *= 1\nx /= 1\nx **= 1",
- "replacement": "x+= 2\nx -= 1\nx *= 1\nx /= 1\nx **= 1",
+ "replacement": "x+= 2\nx -= 1\nx *= 1\nx /= 1\nx **= 1"
},
{
"syntax": "conditional-assignment",
"insert": "x ||= 5",
- "replacement": "x &&= 7",
+ "replacement": "x &&= 7"
},
{
"syntax": "multiple-assignments",
"insert": "x, y, z = 10, 20, 30",
- "replacement": "x, y = aVariable, 40",
+ "replacement": "x, y = aVariable, 40"
},
{
"syntax": "pseudo-variables",
"insert": "nil\nself\nfalse\ntrue",
- "replacement": "self\nNIL\nTRUE\nFALSE",
+ "replacement": "self\nNIL\nTRUE\nFALSE"
},
{
"syntax": "subshell",
"insert": "`ls -la`",
- "replacement": "`git status`",
+ "replacement": "`git status`"
},
{
"syntax": "hash",
"insert": "{ :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }",
- "replacement": "{ key1: \"changed value\", key2: 2, key3: true }",
+ "replacement": "{ key1: \"changed value\", key2: 2, key3: true }"
},
{
"syntax": "boolean-operator",
"insert": "a || b",
- "replacement": "a && b",
+ "replacement": "a && b"
},
{
"syntax": "relational-operator",
"insert": "x == y\nx != y\nx === y",
- "replacement": "x <=> y\nx =~ y\nx =! y",
+ "replacement": "x <=> y\nx =~ y\nx =! y"
},
{
"syntax": "comparision-operator",
"insert": "x < y\na > b",
- "replacement": "x <= y\na >= b",
+ "replacement": "x <= y\na >= b"
},
{
"syntax": "bitwise-operator",
"insert": "a | b\na >> b\na ^ b",
- "replacement": "a & b\na << b",
+ "replacement": "a & b\na << b"
},
{
"syntax": "ternary",
- "insert": "condition ? case1 : case2",
- "replacement": "if condition then case 1 else case2",
+ "insert": "foo ? case1 : case2",
+ "replacement": "bar ? a : b"
+ },
+ {
+ "syntax": "method-declaration",
+ "insert": "def foo\nend",
+ "replacement": "def bar(a)\n baz\nend"
+ },
+ {
+ "syntax": "method-declaration-params",
+ "template": "def foo{0}\nend",
+ "insert": "(a)",
+ "replacement": "(a, b, c)"
},
{
"syntax": "method-invocation",
"insert": "print\nfoo.bar\nbar",
- "replacement": "print(\"hello world\")\nfoo.bar()\nbar 2, 3\nbar(2, 3)",
+ "replacement": "print(\"hello world\")\nfoo.bar()\nbar 2, 3\nbar(2, 3)"
},
{
- "syntax": "case-statement",
- "insert": "case foo\nwhen bar\nend",
- "replacement": "case foo\nwhen bar\nelse\nend",
+ "syntax": "method-calls",
+ "insert": "x.foo()",
+ "replacement": "bar()"
},
{
"syntax": "class",
"insert": "class Foo < Super\n def test; end\nend",
- "replacement": "class Foo\n def test; end\nend",
+ "replacement": "class Foo\n def test; end\nend"
},
{
"syntax": "module",
- "insert": "module Foo\n class Bar\n def self.test; end\nend\nend",
- "replacement": "class Bar::Foo\nend",
+ "insert": "module Foo\nend",
+ "replacement": "module Foo\n def bar\n end\nend"
},
{
"syntax": "return",
"insert": "return foo",
- "replacement": "return",
+ "replacement": "return"
},
{
"syntax": "yield",
"insert": "yield foo",
- "replacement": "yield",
+ "replacement": "yield"
},
{
"syntax": "while",
"insert": "while foo do\nend\nfoo while run",
- "replacement": "while foo\n bar\nend",
+ "replacement": "while foo\n bar\nend"
},
{
"syntax": "until",
"insert": "until foo do\nend\nfoo until done",
- "replacement": "until foo\n bar\nend",
+ "replacement": "until foo\n bar\nend"
},
{
"syntax": "if",
"insert": "if foo\n bar\nelsif quux\n baz\nelse\n bat\nend",
- "replacement": "if x\nend\nif y then\nend",
+ "replacement": "if x\nend\nif y then\nend"
},
{
"syntax": "unless",
"insert": "unless foo\n bar\nelse\n bat\nend",
- "replacement": "unless x\nend\nunless y then\nend",
+ "replacement": "unless x\nend\nunless y then\nend"
},
{
"syntax": "if-unless-modifiers",
"insert": "print unless foo",
- "replacement": "print if foo",
+ "replacement": "print if foo"
},
{
"syntax": "and-or",
"insert": "foo and bar",
- "replacement": "foo or bar\na or b and c",
+ "replacement": "foo or bar\na or b and c"
},
{
"syntax": "regex",
"insert": "/^(foo|bar[^_])$/i",
- "replacement": "%r/a/\n%rc>",
+ "replacement": "%r/a/\n%rc>"
},
{
"syntax": "array",
"insert": "[ 1, 2, 3]",
- "replacement": "['a', 'b', 'c']",
+ "replacement": "['a', 'b', 'c']"
},
{
"syntax": "percent-array",
"insert": "%w(one two)",
- "replacement": "%W(one #{b} three)",
+ "replacement": "%W(one #{b} three)"
},
{
"syntax": "lambda-dash-rocket",
"insert": "-> (a, b, c) {\n 1\n 2\n}",
- "replacement": "-> { foo }",
+ "replacement": "-> { foo }"
},
{
"syntax": "lambda",
"insert": "lambda { foo }",
- "replacement": "lambda { |x| x + 1 }",
+ "replacement": "lambda { |x| x + 1 }"
},
{
"syntax": "for",
"insert": "for x in y\n f\nend",
- "replacement": "for i in [1,2,3] do\n print i\nend",
+ "replacement": "for i in [1,2,3] do\n print i\nend"
},
{
"syntax": "element-reference",
"insert": "foo[bar]\nfoo[:bar]\nfoo[bar] = 1",
- "replacement": "x[\"b\"]\nx[:\"c\"]",
+ "replacement": "x[\"b\"]\nx[:\"c\"]"
},
{
- "syntax": "control-statements",
- "insert": "begin\n foo\nrescue x\n bar\nelse\n quux\nensure\n baz\nend",
- "replacement": "begin\nend",
+ "syntax": "begin",
+ "template": "def foo\n{0}end",
+ "insert": "begin\nend\n",
+ "replacement": "begin\n puts 'hi'\nend\n"
+ },
+ {
+ "syntax": "else",
+ "template": "begin\n foo()\n{0}end",
+ "insert": "else\n",
+ "replacement": "else\n bar()\n"
+ },
+ {
+ "syntax": "elsif",
+ "template": "if bar\n foo()\n{0}end",
+ "insert": "elsif baz\n",
+ "replacement": "elsif baz\n qoz()\n"
+ },
+ {
+ "syntax": "ensure",
+ "template": "begin\n foo\n{0}end",
+ "insert": "ensure\n",
+ "replacement": "ensure\n bar\n"
+ },
+ {
+ "syntax": "rescue",
+ "template": "begin\n foo\n{0}end",
+ "insert": "rescue x\n",
+ "replacement": "rescue x\n bar\n"
+ },
+ {
+ "syntax": "rescue-empty",
+ "insert": "begin\n foo\nrescue\nend",
+ "replacement": "begin\n foo\nrescue\n bar\nend"
+ },
+ {
+ "syntax": "rescue-last-ex",
+ "insert": "begin\n foo\nrescue Error => x\nend",
+ "replacement": "begin\n foo\nrescue Error => x\n bar\nend"
+ },
+ {
+ "syntax": "rescue-modifier",
+ "insert": "foo rescue nil",
+ "replacement": "foo rescue false"
+ },
+ {
+ "syntax": "rescue-modifier2",
+ "insert": "foo rescue nil",
+ "replacement": "bar rescue nil"
+ },
+ {
+ "syntax": "when",
+ "template": "case foo\n{0}end",
+ "insert": "when bar\n",
+ "replacement": "when bar\n baz\n"
+ },
+ {
+ "syntax": "when-else",
+ "template": "case foo\nwhen bar\n baz\n{0}end",
+ "insert": "else\n",
+ "replacement": "else\n qoz\n"
}
]
}
diff --git a/test/corpus/json/javascript/anonymous-function.json b/test/corpus/json/javascript/anonymous-function.json
index 63b78ff75..7ffe605ab 100644
--- a/test/corpus/json/javascript/anonymous-function.json
+++ b/test/corpus/json/javascript/anonymous-function.json
@@ -131,9 +131,16 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "9e5406166a9e280d7ad6cc8bf570b450e90347a5",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index e69de29..b592868 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -0,0 +1 @@",
+ "+function(a,b) { return a + b; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d7ffd2b2f9e060e93f1acc30e8cf6babd83002bd"
+ "shas": "193d1078ef93cde9a03725d1f4b6a42b856754d3..0f94ee7144066b4bf2e6fb86266fe3980d7c20aa"
}
,{
"testCaseDescription": "javascript-anonymous-function-replacement-insert-test",
@@ -566,9 +573,18 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "d7ffd2b2f9e060e93f1acc30e8cf6babd83002bd",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index b592868..e1de356 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1 +1,3 @@",
+ "+function(b,c) { return b * c; }",
+ "+function(a,b) { return a + b; }",
+ " function(a,b) { return a + b; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c8612009b5d29153c916c644de489394fe0e926f"
+ "shas": "0f94ee7144066b4bf2e6fb86266fe3980d7c20aa..85b50027ed8e318f409ebfdeec95d332e4372c9d"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-insert-test",
@@ -1191,9 +1207,19 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "c8612009b5d29153c916c644de489394fe0e926f",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index e1de356..4ca0d4c 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function(b,c) { return b * c; }",
+ "+function(a,b) { return a + b; }",
+ " function(a,b) { return a + b; }",
+ " function(a,b) { return a + b; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "706f7c74900a7e12c3a4d3213b84a8851e506efe"
+ "shas": "85b50027ed8e318f409ebfdeec95d332e4372c9d..277409950b39db70396ab88d79fef61e6f355cf9"
}
,{
"testCaseDescription": "javascript-anonymous-function-replacement-test",
@@ -1816,9 +1842,19 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "706f7c74900a7e12c3a4d3213b84a8851e506efe",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index 4ca0d4c..e1de356 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function(a,b) { return a + b; }",
+ "+function(b,c) { return b * c; }",
+ " function(a,b) { return a + b; }",
+ " function(a,b) { return a + b; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "33fbd33b9dee1ffe97a03a992231f3b0d536efa1"
+ "shas": "277409950b39db70396ab88d79fef61e6f355cf9..1f70d35c4fc7af5fef2b1f33af11fea8bf74ac64"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-replacement-test",
@@ -2346,9 +2382,19 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "33fbd33b9dee1ffe97a03a992231f3b0d536efa1",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index e1de356..afdaccf 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function(b,c) { return b * c; }",
+ "-function(a,b) { return a + b; }",
+ " function(a,b) { return a + b; }",
+ "+function(b,c) { return b * c; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "20847e86ad60bcd4413d73094a3ce3650c74c414"
+ "shas": "1f70d35c4fc7af5fef2b1f33af11fea8bf74ac64..085a8e51416cd260921607437cf74474535dd1e8"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-test",
@@ -2686,9 +2732,17 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "20847e86ad60bcd4413d73094a3ce3650c74c414",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index afdaccf..9f1856f 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1,2 +1 @@",
+ "-function(a,b) { return a + b; }",
+ " function(b,c) { return b * c; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "39da8cd0e4fe3da04c3feaece752d84d14b46c58"
+ "shas": "085a8e51416cd260921607437cf74474535dd1e8..4dba50c9b3f7e53a052d78885254b1138bd11caa"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-rest-test",
@@ -2823,7 +2877,14 @@
"filePaths": [
"anonymous-function.js"
],
- "sha1": "39da8cd0e4fe3da04c3feaece752d84d14b46c58",
+ "patch": [
+ "diff --git a/anonymous-function.js b/anonymous-function.js",
+ "index 9f1856f..e69de29 100644",
+ "--- a/anonymous-function.js",
+ "+++ b/anonymous-function.js",
+ "@@ -1 +0,0 @@",
+ "-function(b,c) { return b * c; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e983da932d1dc1b84e8aef2db57c2cf7a5a9f208"
+ "shas": "4dba50c9b3f7e53a052d78885254b1138bd11caa..b6fb98d6c49e32009671313bca0c3f8b9f01f8d4"
}]
diff --git a/test/corpus/json/javascript/anonymous-parameterless-function.json b/test/corpus/json/javascript/anonymous-parameterless-function.json
index 4a44c7043..9324a1686 100644
--- a/test/corpus/json/javascript/anonymous-parameterless-function.json
+++ b/test/corpus/json/javascript/anonymous-parameterless-function.json
@@ -101,9 +101,16 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "e983da932d1dc1b84e8aef2db57c2cf7a5a9f208",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index e69de29..4a26ae8 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -0,0 +1 @@",
+ "+function() { return 'hi'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "235fe610b8d548bd854d149b3b1011ecc3f139a5"
+ "shas": "b6fb98d6c49e32009671313bca0c3f8b9f01f8d4..90907a7b09e75e065f750c20ebfd4e4dc338606c"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test",
@@ -416,9 +423,18 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "235fe610b8d548bd854d149b3b1011ecc3f139a5",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index 4a26ae8..c31dd4b 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1 +1,3 @@",
+ "+function() { return 'hello'; }",
+ "+function() { return 'hi'; }",
+ " function() { return 'hi'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7466d0c40a9639bae9a47d37d6f06fa58669250c"
+ "shas": "90907a7b09e75e065f750c20ebfd4e4dc338606c..7502e8aa7b1be8e9fccfb8a13d7a4198e2e6bfaf"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test",
@@ -855,9 +871,19 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "7466d0c40a9639bae9a47d37d6f06fa58669250c",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index c31dd4b..6b1efa4 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function() { return 'hello'; }",
+ "+function() { return 'hi'; }",
+ " function() { return 'hi'; }",
+ " function() { return 'hi'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3ed63ee63caa4e137fa50777805eddf9a6c50f94"
+ "shas": "7502e8aa7b1be8e9fccfb8a13d7a4198e2e6bfaf..bd22ef3539284345f997eb0db0dc499250191ec8"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test",
@@ -1294,9 +1320,19 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "3ed63ee63caa4e137fa50777805eddf9a6c50f94",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index 6b1efa4..c31dd4b 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function() { return 'hi'; }",
+ "+function() { return 'hello'; }",
+ " function() { return 'hi'; }",
+ " function() { return 'hi'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2c4006877c436df9dbe28fafd221eff636313c88"
+ "shas": "bd22ef3539284345f997eb0db0dc499250191ec8..0e4f4ffdb14d066c264de5949c5676a620be32f3"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test",
@@ -1674,9 +1710,19 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "2c4006877c436df9dbe28fafd221eff636313c88",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index c31dd4b..b8e05c0 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function() { return 'hello'; }",
+ "-function() { return 'hi'; }",
+ " function() { return 'hi'; }",
+ "+function() { return 'hello'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c33a9110889ab99a82f154fb6ca02ec581ea5884"
+ "shas": "0e4f4ffdb14d066c264de5949c5676a620be32f3..d03a8c9a2bf8e64daedb6d617fa97ff6d8215b64"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-test",
@@ -1924,9 +1970,17 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "c33a9110889ab99a82f154fb6ca02ec581ea5884",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index b8e05c0..ce1ef83 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1,2 +1 @@",
+ "-function() { return 'hi'; }",
+ " function() { return 'hello'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "96a0cf7c7a0f3d825346706ba70aa454e66da430"
+ "shas": "d03a8c9a2bf8e64daedb6d617fa97ff6d8215b64..61b53588ccb1690db4be3c566dc13037f86e2631"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test",
@@ -2031,7 +2085,14 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
- "sha1": "96a0cf7c7a0f3d825346706ba70aa454e66da430",
+ "patch": [
+ "diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
+ "index ce1ef83..e69de29 100644",
+ "--- a/anonymous-parameterless-function.js",
+ "+++ b/anonymous-parameterless-function.js",
+ "@@ -1 +0,0 @@",
+ "-function() { return 'hello'; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "042a288ab3f8ef27e53f4354c48b71c03de8b2d2"
+ "shas": "61b53588ccb1690db4be3c566dc13037f86e2631..d85c24526768ef13d44a0e8cce5aefe270e43c4a"
}]
diff --git a/test/corpus/json/javascript/array.json b/test/corpus/json/javascript/array.json
index 0549f0451..da4279943 100644
--- a/test/corpus/json/javascript/array.json
+++ b/test/corpus/json/javascript/array.json
@@ -83,9 +83,16 @@
"filePaths": [
"array.js"
],
- "sha1": "7ef0c70c25e5118939b0c4d0ca40f60822f9589f",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index e69de29..3335582 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -0,0 +1 @@",
+ "+[ \"item1\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "41a1c86a6592e7d0f54d78074cdb878c5af47d12"
+ "shas": "f24de0d24746d9f2408eda661698733705bd8a14..cc01ed254daa10d4e01b67e7d04ba5432020ca79"
}
,{
"testCaseDescription": "javascript-array-replacement-insert-test",
@@ -333,9 +340,18 @@
"filePaths": [
"array.js"
],
- "sha1": "41a1c86a6592e7d0f54d78074cdb878c5af47d12",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index 3335582..cf37d7c 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1 +1,3 @@",
+ "+[ \"item1\", \"item2\" ];",
+ "+[ \"item1\" ];",
+ " [ \"item1\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "468b94336a065dd85554aa55b2c70c084d5d1fb3"
+ "shas": "cc01ed254daa10d4e01b67e7d04ba5432020ca79..c32c125fbf94e5f446da6b4bcc71ab83790e3eb8"
}
,{
"testCaseDescription": "javascript-array-delete-insert-test",
@@ -670,9 +686,19 @@
"filePaths": [
"array.js"
],
- "sha1": "468b94336a065dd85554aa55b2c70c084d5d1fb3",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index cf37d7c..c2cb17f 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1,3 +1,3 @@",
+ "-[ \"item1\", \"item2\" ];",
+ "+[ \"item1\" ];",
+ " [ \"item1\" ];",
+ " [ \"item1\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e36d978a4b404cf95874ff6d568b205f0254ee07"
+ "shas": "c32c125fbf94e5f446da6b4bcc71ab83790e3eb8..439bb224c0c4fe667a42c61bc319ca7891a035df"
}
,{
"testCaseDescription": "javascript-array-replacement-test",
@@ -1007,9 +1033,19 @@
"filePaths": [
"array.js"
],
- "sha1": "e36d978a4b404cf95874ff6d568b205f0254ee07",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index c2cb17f..cf37d7c 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1,3 +1,3 @@",
+ "-[ \"item1\" ];",
+ "+[ \"item1\", \"item2\" ];",
+ " [ \"item1\" ];",
+ " [ \"item1\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c81dbb1d20a5ecbe43d726fd7d9aa28ddde1f46b"
+ "shas": "439bb224c0c4fe667a42c61bc319ca7891a035df..d19df2f2b147510e83c6f72fc96759a8fc316015"
}
,{
"testCaseDescription": "javascript-array-delete-replacement-test",
@@ -1311,9 +1347,19 @@
"filePaths": [
"array.js"
],
- "sha1": "c81dbb1d20a5ecbe43d726fd7d9aa28ddde1f46b",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index cf37d7c..a4d92b8 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1,3 +1,2 @@",
+ "-[ \"item1\", \"item2\" ];",
+ "-[ \"item1\" ];",
+ " [ \"item1\" ];",
+ "+[ \"item1\", \"item2\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5089a63a20278b07d8a84c3bb0561861084174d2"
+ "shas": "d19df2f2b147510e83c6f72fc96759a8fc316015..8f07abcf89121cd177cd3d238c1ffe36321da00b"
}
,{
"testCaseDescription": "javascript-array-delete-test",
@@ -1521,9 +1567,17 @@
"filePaths": [
"array.js"
],
- "sha1": "5089a63a20278b07d8a84c3bb0561861084174d2",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index a4d92b8..7f2f50e 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1,2 +1 @@",
+ "-[ \"item1\" ];",
+ " [ \"item1\", \"item2\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "35178bc55a46231d0809f9ece4d92feaaff3b0f4"
+ "shas": "8f07abcf89121cd177cd3d238c1ffe36321da00b..9bfceef09e8693663faf7ed767e2526379aa7d28"
}
,{
"testCaseDescription": "javascript-array-delete-rest-test",
@@ -1617,7 +1671,14 @@
"filePaths": [
"array.js"
],
- "sha1": "35178bc55a46231d0809f9ece4d92feaaff3b0f4",
+ "patch": [
+ "diff --git a/array.js b/array.js",
+ "index 7f2f50e..e69de29 100644",
+ "--- a/array.js",
+ "+++ b/array.js",
+ "@@ -1 +0,0 @@",
+ "-[ \"item1\", \"item2\" ];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "aab3cdb03018b80452f88033908dda159df29b58"
+ "shas": "9bfceef09e8693663faf7ed767e2526379aa7d28..47efa692005800aae87fccdba3a089c87d9c46f1"
}]
diff --git a/test/corpus/json/javascript/arrow-function.json b/test/corpus/json/javascript/arrow-function.json
index 2c4cbdf76..8bb823204 100644
--- a/test/corpus/json/javascript/arrow-function.json
+++ b/test/corpus/json/javascript/arrow-function.json
@@ -115,9 +115,16 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "a83003e88deb30e0a3c4f7d369c0aa0a24986a82",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index e69de29..9ef167c 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -0,0 +1 @@",
+ "+(f, g) => { return h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "748c19e755891936f23fcc45d63825d0b39b8d12"
+ "shas": "4a56270744e8c9a123c828e7ab9409789ab51e5b..354952d5bb12d69a77c300031873d5f24cdfb8ec"
}
,{
"testCaseDescription": "javascript-arrow-function-replacement-insert-test",
@@ -486,9 +493,18 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "748c19e755891936f23fcc45d63825d0b39b8d12",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index 9ef167c..92dea6f 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1 +1,3 @@",
+ "+(f, g) => { return g; };",
+ "+(f, g) => { return h; };",
+ " (f, g) => { return h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "03d5ae84846ecccdaa9b48d36cf3f8fece475f30"
+ "shas": "354952d5bb12d69a77c300031873d5f24cdfb8ec..e14d6bef489fc103f67915f63487672c56e71171"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-insert-test",
@@ -1009,9 +1025,19 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "03d5ae84846ecccdaa9b48d36cf3f8fece475f30",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index 92dea6f..8f5bb51 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-(f, g) => { return g; };",
+ "+(f, g) => { return h; };",
+ " (f, g) => { return h; };",
+ " (f, g) => { return h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "96cca3f2e5970665cae1a91c1561692e14d7c649"
+ "shas": "e14d6bef489fc103f67915f63487672c56e71171..07cd8aacb36d8bff27fa08fa74711bd4dc234bf9"
}
,{
"testCaseDescription": "javascript-arrow-function-replacement-test",
@@ -1532,9 +1558,19 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "96cca3f2e5970665cae1a91c1561692e14d7c649",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index 8f5bb51..92dea6f 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-(f, g) => { return h; };",
+ "+(f, g) => { return g; };",
+ " (f, g) => { return h; };",
+ " (f, g) => { return h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c4dc9c992b9d50f5a2b8449ad66f3212b1fecea1"
+ "shas": "07cd8aacb36d8bff27fa08fa74711bd4dc234bf9..04e144b29b788332a7b841f72d3a54e54bf177a1"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-replacement-test",
@@ -1982,9 +2018,19 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "c4dc9c992b9d50f5a2b8449ad66f3212b1fecea1",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index 92dea6f..acab9a9 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-(f, g) => { return g; };",
+ "-(f, g) => { return h; };",
+ " (f, g) => { return h; };",
+ "+(f, g) => { return g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b0fbc4bce466fcc142008aa26199d0102f2d4e15"
+ "shas": "04e144b29b788332a7b841f72d3a54e54bf177a1..99d26e538f591473bc4c23e991a8fb4addcb2c15"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-test",
@@ -2274,9 +2320,17 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "b0fbc4bce466fcc142008aa26199d0102f2d4e15",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index acab9a9..ef1be25 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1,2 +1 @@",
+ "-(f, g) => { return h; };",
+ " (f, g) => { return g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c37b9ca68b3e243466b5a868dfec1fca37a1988c"
+ "shas": "99d26e538f591473bc4c23e991a8fb4addcb2c15..1327f9cc5b23ac1be93532b0a8d3f096044105f9"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-rest-test",
@@ -2395,7 +2449,14 @@
"filePaths": [
"arrow-function.js"
],
- "sha1": "c37b9ca68b3e243466b5a868dfec1fca37a1988c",
+ "patch": [
+ "diff --git a/arrow-function.js b/arrow-function.js",
+ "index ef1be25..e69de29 100644",
+ "--- a/arrow-function.js",
+ "+++ b/arrow-function.js",
+ "@@ -1 +0,0 @@",
+ "-(f, g) => { return g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "cbcb5d062890692a2a789b510fe5ca42f93fbae0"
+ "shas": "1327f9cc5b23ac1be93532b0a8d3f096044105f9..a52e2d614f9e9504970732cbc2d5f9c933eb061f"
}]
diff --git a/test/corpus/json/javascript/assignment.json b/test/corpus/json/javascript/assignment.json
index 9a4a8a90d..7778e53c3 100644
--- a/test/corpus/json/javascript/assignment.json
+++ b/test/corpus/json/javascript/assignment.json
@@ -90,9 +90,16 @@
"filePaths": [
"assignment.js"
],
- "sha1": "5ab51e5a23cbcc433c36acf01b0f85eb614f11ab",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index e69de29..6882fe5 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -0,0 +1 @@",
+ "+x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d746d74163a2149047d8462db5ad16c31dd73765"
+ "shas": "aa5f6a7c2031a5c8823a005dffbe948bd997e140..f5d468945963e06f4af8f37da1f4b43c6f7dc89b"
}
,{
"testCaseDescription": "javascript-assignment-replacement-insert-test",
@@ -361,9 +368,18 @@
"filePaths": [
"assignment.js"
],
- "sha1": "d746d74163a2149047d8462db5ad16c31dd73765",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index 6882fe5..fb4cba4 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1 +1,3 @@",
+ "+x = 1;",
+ "+x = 0;",
+ " x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3515e1962f311723e5b2f7f1c126ebf69ad44a0c"
+ "shas": "f5d468945963e06f4af8f37da1f4b43c6f7dc89b..079aadf7d837be3f3cbaa970bda8df4f24ca9dfd"
}
,{
"testCaseDescription": "javascript-assignment-delete-insert-test",
@@ -734,9 +750,19 @@
"filePaths": [
"assignment.js"
],
- "sha1": "3515e1962f311723e5b2f7f1c126ebf69ad44a0c",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index fb4cba4..42e16c6 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-x = 1;",
+ "+x = 0;",
+ " x = 0;",
+ " x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "da6c1843516fd250cd1f0261e82968359ed86e77"
+ "shas": "079aadf7d837be3f3cbaa970bda8df4f24ca9dfd..59dc3f7b9aa4067d998fe7a7167d25a879597bbe"
}
,{
"testCaseDescription": "javascript-assignment-replacement-test",
@@ -1107,9 +1133,19 @@
"filePaths": [
"assignment.js"
],
- "sha1": "da6c1843516fd250cd1f0261e82968359ed86e77",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index 42e16c6..fb4cba4 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-x = 0;",
+ "+x = 1;",
+ " x = 0;",
+ " x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fdf51438dbad7829421ddd80dcaf88c6b0ff2bd2"
+ "shas": "59dc3f7b9aa4067d998fe7a7167d25a879597bbe..7a05860458ff8fe37877bd3105ddd6cae586b0cf"
}
,{
"testCaseDescription": "javascript-assignment-delete-replacement-test",
@@ -1432,9 +1468,19 @@
"filePaths": [
"assignment.js"
],
- "sha1": "fdf51438dbad7829421ddd80dcaf88c6b0ff2bd2",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index fb4cba4..11fe15d 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1,3 +1,2 @@",
+ "-x = 1;",
+ "-x = 0;",
+ " x = 0;",
+ "+x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c78b33549c791479368879700d687f552871eeb2"
+ "shas": "7a05860458ff8fe37877bd3105ddd6cae586b0cf..b815835af80b7e47423649f4ac97477d00069b02"
}
,{
"testCaseDescription": "javascript-assignment-delete-test",
@@ -1649,9 +1695,17 @@
"filePaths": [
"assignment.js"
],
- "sha1": "c78b33549c791479368879700d687f552871eeb2",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index 11fe15d..198b8f8 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1,2 +1 @@",
+ "-x = 0;",
+ " x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "64ab925954d584de96ebd92f27cfdeb8c5f4028c"
+ "shas": "b815835af80b7e47423649f4ac97477d00069b02..5524702d577596f2531f09de1af7369cbc54b582"
}
,{
"testCaseDescription": "javascript-assignment-delete-rest-test",
@@ -1745,7 +1799,14 @@
"filePaths": [
"assignment.js"
],
- "sha1": "64ab925954d584de96ebd92f27cfdeb8c5f4028c",
+ "patch": [
+ "diff --git a/assignment.js b/assignment.js",
+ "index 198b8f8..e69de29 100644",
+ "--- a/assignment.js",
+ "+++ b/assignment.js",
+ "@@ -1 +0,0 @@",
+ "-x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "48190229aaa2c5d5ca3796814538a309e3b261d4"
+ "shas": "5524702d577596f2531f09de1af7369cbc54b582..30a517ace94526eae9f09618d7cc587cdbb96c25"
}]
diff --git a/test/corpus/json/javascript/bitwise-operator.json b/test/corpus/json/javascript/bitwise-operator.json
index 99966fc9c..a7d167c45 100644
--- a/test/corpus/json/javascript/bitwise-operator.json
+++ b/test/corpus/json/javascript/bitwise-operator.json
@@ -90,9 +90,16 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "0afa7defe7188cc37bb1b58e3f66f45151021f83",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index e69de29..021cf6a 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -0,0 +1 @@",
+ "+i >> j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "45e567a562ba976e38a4f9f216e445cfebafd3bf"
+ "shas": "94fca5fc215c9c7199b86ef4da0ad543ca630b92..99ba41aa0041a3105e46827e137d5105469bddeb"
}
,{
"testCaseDescription": "javascript-bitwise-operator-replacement-insert-test",
@@ -361,9 +368,18 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "45e567a562ba976e38a4f9f216e445cfebafd3bf",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index 021cf6a..3e0b6c1 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1 +1,3 @@",
+ "+i >> k;",
+ "+i >> j;",
+ " i >> j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7617f84640706b4cb9b1b83a6ab267b29bb7cd3d"
+ "shas": "99ba41aa0041a3105e46827e137d5105469bddeb..202e42ebe72f74a25c429078725af9921fe65545"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-insert-test",
@@ -734,9 +750,19 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "7617f84640706b4cb9b1b83a6ab267b29bb7cd3d",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index 3e0b6c1..18853d1 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i >> k;",
+ "+i >> j;",
+ " i >> j;",
+ " i >> j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "460773dcf9db1fe2a14d6f11d12f5fcfb3ffb69f"
+ "shas": "202e42ebe72f74a25c429078725af9921fe65545..5f5111c80d08d0bbc7a1a2661d1a4ead7021937e"
}
,{
"testCaseDescription": "javascript-bitwise-operator-replacement-test",
@@ -1107,9 +1133,19 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "460773dcf9db1fe2a14d6f11d12f5fcfb3ffb69f",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index 18853d1..3e0b6c1 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i >> j;",
+ "+i >> k;",
+ " i >> j;",
+ " i >> j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "97b7eecc8a95fccf545b88f282f1ff338d2330c5"
+ "shas": "5f5111c80d08d0bbc7a1a2661d1a4ead7021937e..beeda50d15e6e13cfd9a03d83f30a410dbc07fe9"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-replacement-test",
@@ -1432,9 +1468,19 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "97b7eecc8a95fccf545b88f282f1ff338d2330c5",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index 3e0b6c1..ee7d8de 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-i >> k;",
+ "-i >> j;",
+ " i >> j;",
+ "+i >> k;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c2e4e0974afe3f5ad9ea072ec0bb31ad9cbcfd2d"
+ "shas": "beeda50d15e6e13cfd9a03d83f30a410dbc07fe9..02065a82a63470d29c655c04adeebc72961353d0"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-test",
@@ -1649,9 +1695,17 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "c2e4e0974afe3f5ad9ea072ec0bb31ad9cbcfd2d",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index ee7d8de..2800c8c 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1,2 +1 @@",
+ "-i >> j;",
+ " i >> k;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2b49695d0b6559ace16a084f3024d1710869a62c"
+ "shas": "02065a82a63470d29c655c04adeebc72961353d0..59a5ae59bc44cac921e21f84a88c8ee0f0690a47"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-rest-test",
@@ -1745,7 +1799,14 @@
"filePaths": [
"bitwise-operator.js"
],
- "sha1": "2b49695d0b6559ace16a084f3024d1710869a62c",
+ "patch": [
+ "diff --git a/bitwise-operator.js b/bitwise-operator.js",
+ "index 2800c8c..e69de29 100644",
+ "--- a/bitwise-operator.js",
+ "+++ b/bitwise-operator.js",
+ "@@ -1 +0,0 @@",
+ "-i >> k;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a919283c34de839a761ede23220cbfb06d95fc5e"
+ "shas": "59a5ae59bc44cac921e21f84a88c8ee0f0690a47..ba72732ac272c8ae8487ba0af9045dea54eb02d9"
}]
diff --git a/test/corpus/json/javascript/boolean-operator.json b/test/corpus/json/javascript/boolean-operator.json
index cc97b3808..b944594b6 100644
--- a/test/corpus/json/javascript/boolean-operator.json
+++ b/test/corpus/json/javascript/boolean-operator.json
@@ -90,9 +90,16 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "714e5a0dfd44d739d9669ab32c1f32160436e5a2",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index e69de29..7280a98 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -0,0 +1 @@",
+ "+i || j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a47c5c2990f72c9bde5678f2d49625988cc01fb1"
+ "shas": "b0194f4ccae027de9b6fbbc4ceefe070cf51555c..c8ce4905edb0321dfaf25203714eda8d05133dc0"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-insert-test",
@@ -361,9 +368,18 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "a47c5c2990f72c9bde5678f2d49625988cc01fb1",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index 7280a98..fe3f306 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1 +1,3 @@",
+ "+i && j;",
+ "+i || j;",
+ " i || j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f3faa41589c7adf9a27099b5837c7748f8fb9f39"
+ "shas": "c8ce4905edb0321dfaf25203714eda8d05133dc0..018d110adadddb7b94c0c87869f4ef32d9f38bc8"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-insert-test",
@@ -732,9 +748,19 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "f3faa41589c7adf9a27099b5837c7748f8fb9f39",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index fe3f306..273c0ee 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i && j;",
+ "+i || j;",
+ " i || j;",
+ " i || j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d9f0b3ca5a28ba110599c1fb3e50f13959552194"
+ "shas": "018d110adadddb7b94c0c87869f4ef32d9f38bc8..a6577b774ffd0e26986c4e60b951efb7b2680f5c"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-test",
@@ -1103,9 +1129,19 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "d9f0b3ca5a28ba110599c1fb3e50f13959552194",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index 273c0ee..fe3f306 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i || j;",
+ "+i && j;",
+ " i || j;",
+ " i || j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9736ab252f67c2f14852335eee08c0096ff5231c"
+ "shas": "a6577b774ffd0e26986c4e60b951efb7b2680f5c..742092b6c51172647d7fae976b8b8a5f90842bcc"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-replacement-test",
@@ -1424,9 +1460,19 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "9736ab252f67c2f14852335eee08c0096ff5231c",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index fe3f306..7f4873c 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-i && j;",
+ "-i || j;",
+ " i || j;",
+ "+i && j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "773c0d402eeee97cb1bae0e3b92e409122ec7ca0"
+ "shas": "742092b6c51172647d7fae976b8b8a5f90842bcc..2d12e99c24f6e12742ce6c4456d2ee36b8506d95"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-test",
@@ -1641,9 +1687,17 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "773c0d402eeee97cb1bae0e3b92e409122ec7ca0",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index 7f4873c..c6921d1 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1,2 +1 @@",
+ "-i || j;",
+ " i && j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "65134b28c2f993cadb668adb4633129652739ad5"
+ "shas": "2d12e99c24f6e12742ce6c4456d2ee36b8506d95..c5a063d347caaa73b7d767f02acda08a144928c0"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-rest-test",
@@ -1737,7 +1791,14 @@
"filePaths": [
"boolean-operator.js"
],
- "sha1": "65134b28c2f993cadb668adb4633129652739ad5",
+ "patch": [
+ "diff --git a/boolean-operator.js b/boolean-operator.js",
+ "index c6921d1..e69de29 100644",
+ "--- a/boolean-operator.js",
+ "+++ b/boolean-operator.js",
+ "@@ -1 +0,0 @@",
+ "-i && j;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0afa7defe7188cc37bb1b58e3f66f45151021f83"
+ "shas": "c5a063d347caaa73b7d767f02acda08a144928c0..94fca5fc215c9c7199b86ef4da0ad543ca630b92"
}]
diff --git a/test/corpus/json/javascript/chained-callbacks.json b/test/corpus/json/javascript/chained-callbacks.json
index d5c0cf82b..67077ca31 100644
--- a/test/corpus/json/javascript/chained-callbacks.json
+++ b/test/corpus/json/javascript/chained-callbacks.json
@@ -147,9 +147,16 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "a609ccfbb04fee2d680c3b02f4941f96a046b2bc",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index e69de29..ce9ee1e 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -0,0 +1 @@",
+ "+this.map(function (a) { return a.b; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c110a5f0b39ce2dc514ffd1453063b43ec95e466"
+ "shas": "20036c5dfbcbfda6adb2ac623f76a2d33319daff..8fe67e615790750c81a0d0cf671039fd04874196"
}
,{
"testCaseDescription": "javascript-chained-callbacks-replacement-insert-test",
@@ -646,9 +653,18 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "c110a5f0b39ce2dc514ffd1453063b43ec95e466",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index ce9ee1e..acba744 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1 +1,3 @@",
+ "+this.reduce(function (a) { return b.a; })",
+ "+this.map(function (a) { return a.b; })",
+ " this.map(function (a) { return a.b; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "095376c8b63a9e4b2bbb728e2b8334213cf92aae"
+ "shas": "8fe67e615790750c81a0d0cf671039fd04874196..2a557ecea000afb29ccc7a685858096c6eee76a3"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-insert-test",
@@ -1365,9 +1381,19 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "095376c8b63a9e4b2bbb728e2b8334213cf92aae",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index acba744..7390534 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1,3 +1,3 @@",
+ "-this.reduce(function (a) { return b.a; })",
+ "+this.map(function (a) { return a.b; })",
+ " this.map(function (a) { return a.b; })",
+ " this.map(function (a) { return a.b; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fdf860c9575f6e38eecda81c8f25fe231f9dd909"
+ "shas": "2a557ecea000afb29ccc7a685858096c6eee76a3..11717a449f96cc2edba70e66ebe01b4f23cd9cc7"
}
,{
"testCaseDescription": "javascript-chained-callbacks-replacement-test",
@@ -2084,9 +2110,19 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "fdf860c9575f6e38eecda81c8f25fe231f9dd909",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index 7390534..acba744 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1,3 +1,3 @@",
+ "-this.map(function (a) { return a.b; })",
+ "+this.reduce(function (a) { return b.a; })",
+ " this.map(function (a) { return a.b; })",
+ " this.map(function (a) { return a.b; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b10fbaa585ddf5cb8ed9c069c245c61ebcced1c6"
+ "shas": "11717a449f96cc2edba70e66ebe01b4f23cd9cc7..0cac26668c9121a11276917ab985c409a8091507"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-replacement-test",
@@ -2694,9 +2730,19 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "b10fbaa585ddf5cb8ed9c069c245c61ebcced1c6",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index acba744..c4db432 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1,3 +1,2 @@",
+ "-this.reduce(function (a) { return b.a; })",
+ "-this.map(function (a) { return a.b; })",
+ " this.map(function (a) { return a.b; })",
+ "+this.reduce(function (a) { return b.a; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d66e586fa9b196b8a042de2542883c1db861997c"
+ "shas": "0cac26668c9121a11276917ab985c409a8091507..f00a27acc2ab003cdeb75993917c80427380f75a"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-test",
@@ -3082,9 +3128,17 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "d66e586fa9b196b8a042de2542883c1db861997c",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index c4db432..e593419 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1,2 +1 @@",
+ "-this.map(function (a) { return a.b; })",
+ " this.reduce(function (a) { return b.a; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "600712840ee74b3811d23807fbc00e6dbdc2b682"
+ "shas": "f00a27acc2ab003cdeb75993917c80427380f75a..ee5b62d892c81a79ad65ad30e017ee7f983b46fb"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-rest-test",
@@ -3235,7 +3289,14 @@
"filePaths": [
"chained-callbacks.js"
],
- "sha1": "600712840ee74b3811d23807fbc00e6dbdc2b682",
+ "patch": [
+ "diff --git a/chained-callbacks.js b/chained-callbacks.js",
+ "index e593419..e69de29 100644",
+ "--- a/chained-callbacks.js",
+ "+++ b/chained-callbacks.js",
+ "@@ -1 +0,0 @@",
+ "-this.reduce(function (a) { return b.a; })"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "28e5cd02261633e062e3045a97dd37064d506a0c"
+ "shas": "ee5b62d892c81a79ad65ad30e017ee7f983b46fb..2f1a5ed4016f7e817cb5b1b4839bb64deecd8042"
}]
diff --git a/test/corpus/json/javascript/chained-property-access.json b/test/corpus/json/javascript/chained-property-access.json
index a5fd9b12a..b8d77c124 100644
--- a/test/corpus/json/javascript/chained-property-access.json
+++ b/test/corpus/json/javascript/chained-property-access.json
@@ -168,9 +168,16 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "4986fadfc0f8ecf1f3b66745c95cf2b6ab739abb",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index e69de29..5914a55 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -0,0 +1 @@",
+ "+return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "25eb51acf1eed4a4b9c3196051d7cdb1d46389c8"
+ "shas": "6a24d1bc284fee3110e5699439106922f5381fd5..f3f2a6e1032364aab733b4a8ed87fa66fe71cd40"
}
,{
"testCaseDescription": "javascript-chained-property-access-replacement-insert-test",
@@ -751,9 +758,18 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "25eb51acf1eed4a4b9c3196051d7cdb1d46389c8",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 5914a55..7095976 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1 +1,3 @@",
+ "+return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
+ "+return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d252b76e97f70f6727fb14db2f6969441bbff8ae"
+ "shas": "f3f2a6e1032364aab733b4a8ed87fa66fe71cd40..7d1949aa8a939002afd35d7388419b83ff514a26"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-insert-test",
@@ -1594,9 +1610,19 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "d252b76e97f70f6727fb14db2f6969441bbff8ae",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 7095976..98df938 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1,3 +1,3 @@",
+ "-return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
+ "+return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0579f4b655a37b6749ed9af5ee6e6d8f6fd87ac8"
+ "shas": "7d1949aa8a939002afd35d7388419b83ff514a26..6e2dc74e68e53734e0a44bdd2397d55c37b770e2"
}
,{
"testCaseDescription": "javascript-chained-property-access-replacement-test",
@@ -2437,9 +2463,19 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "0579f4b655a37b6749ed9af5ee6e6d8f6fd87ac8",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 98df938..7095976 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1,3 +1,3 @@",
+ "-return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ "+return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "eef2234271dc5326229612124e94aa6968bb3ed5"
+ "shas": "6e2dc74e68e53734e0a44bdd2397d55c37b770e2..cdb6f7928a5ab9445c48fd99678565f10d1e0b0b"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-replacement-test",
@@ -3152,9 +3188,19 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "eef2234271dc5326229612124e94aa6968bb3ed5",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 7095976..7b764ca 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1,3 +1,2 @@",
+ "-return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
+ "-return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ "+return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6c38010cddf9e0c0aa52feba073551df81f51f36"
+ "shas": "cdb6f7928a5ab9445c48fd99678565f10d1e0b0b..d26157472f6fc6ea0ef66c22b3dac195cdd5006a"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-test",
@@ -3603,9 +3649,17 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "6c38010cddf9e0c0aa52feba073551df81f51f36",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 7b764ca..5d6d3a0 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1,2 +1 @@",
+ "-return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
+ " return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e3bb57977f19bcf175c82ce3796d59d687c640bf"
+ "shas": "d26157472f6fc6ea0ef66c22b3dac195cdd5006a..a85470721ab757c33254d805cf99d43de95a2d23"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-rest-test",
@@ -3777,7 +3831,14 @@
"filePaths": [
"chained-property-access.js"
],
- "sha1": "e3bb57977f19bcf175c82ce3796d59d687c640bf",
+ "patch": [
+ "diff --git a/chained-property-access.js b/chained-property-access.js",
+ "index 5d6d3a0..e69de29 100644",
+ "--- a/chained-property-access.js",
+ "+++ b/chained-property-access.js",
+ "@@ -1 +0,0 @@",
+ "-return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a609ccfbb04fee2d680c3b02f4941f96a046b2bc"
+ "shas": "a85470721ab757c33254d805cf99d43de95a2d23..20036c5dfbcbfda6adb2ac623f76a2d33319daff"
}]
diff --git a/test/corpus/json/javascript/class.json b/test/corpus/json/javascript/class.json
index 0666a4db7..6fee9e84e 100644
--- a/test/corpus/json/javascript/class.json
+++ b/test/corpus/json/javascript/class.json
@@ -200,9 +200,16 @@
"filePaths": [
"class.js"
],
- "sha1": "2f777027985687b45cb77235606c630008823245",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index e69de29..8f6ae64 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -0,0 +1 @@",
+ "+class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "80a58f6c1b669f6a04bd59d52f62b831e15808b1"
+ "shas": "025ac2dcb7ae8e622fb5a7f0508e2ec9e15604f8..b8c0b35327672fc19a3bbbb950aa826d0b501b1d"
}
,{
"testCaseDescription": "javascript-class-replacement-insert-test",
@@ -911,9 +918,18 @@
"filePaths": [
"class.js"
],
- "sha1": "80a58f6c1b669f6a04bd59d52f62b831e15808b1",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index 8f6ae64..b509437 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1 +1,3 @@",
+ "+class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
+ "+class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b7831153afe71c85593498dd9e64b801a399a2b8"
+ "shas": "b8c0b35327672fc19a3bbbb950aa826d0b501b1d..8385c4226c156fe5e6bf67a99d00305e085e535c"
}
,{
"testCaseDescription": "javascript-class-delete-insert-test",
@@ -1948,9 +1964,19 @@
"filePaths": [
"class.js"
],
- "sha1": "b7831153afe71c85593498dd9e64b801a399a2b8",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index b509437..c4f5c91 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1,3 +1,3 @@",
+ "-class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
+ "+class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d4e80d7da5b32850f70a695785f60e3c5da4522e"
+ "shas": "8385c4226c156fe5e6bf67a99d00305e085e535c..ba68e53cd03ffdc79c72cd1d14aff85ac2bcbb6d"
}
,{
"testCaseDescription": "javascript-class-replacement-test",
@@ -2985,9 +3011,19 @@
"filePaths": [
"class.js"
],
- "sha1": "d4e80d7da5b32850f70a695785f60e3c5da4522e",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index c4f5c91..b509437 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1,3 +1,3 @@",
+ "-class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ "+class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b41e347446b8879cd1f819296ff1602b45029151"
+ "shas": "ba68e53cd03ffdc79c72cd1d14aff85ac2bcbb6d..ba852685e6014e0c26c2a092de5c242d5c3d34fc"
}
,{
"testCaseDescription": "javascript-class-delete-replacement-test",
@@ -3860,9 +3896,19 @@
"filePaths": [
"class.js"
],
- "sha1": "b41e347446b8879cd1f819296ff1602b45029151",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index b509437..b1ef404 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1,3 +1,2 @@",
+ "-class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
+ "-class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ "+class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b84b6e1e2641418e8341aa0a86de72f3efed6b37"
+ "shas": "ba852685e6014e0c26c2a092de5c242d5c3d34fc..6ebb5eb0cca061d650120b97379df9a26bc1a7c3"
}
,{
"testCaseDescription": "javascript-class-delete-test",
@@ -4407,9 +4453,17 @@
"filePaths": [
"class.js"
],
- "sha1": "b84b6e1e2641418e8341aa0a86de72f3efed6b37",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index b1ef404..2c17f72 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1,2 +1 @@",
+ "-class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
+ " class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "917a53c4766090f418622e6a9c06c8ad193447d0"
+ "shas": "6ebb5eb0cca061d650120b97379df9a26bc1a7c3..b990bf8d8e2680f56bc1fb39f8f36750ba4ba7fb"
}
,{
"testCaseDescription": "javascript-class-delete-rest-test",
@@ -4613,7 +4667,14 @@
"filePaths": [
"class.js"
],
- "sha1": "917a53c4766090f418622e6a9c06c8ad193447d0",
+ "patch": [
+ "diff --git a/class.js b/class.js",
+ "index 2c17f72..e69de29 100644",
+ "--- a/class.js",
+ "+++ b/class.js",
+ "@@ -1 +0,0 @@",
+ "-class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7ef0c70c25e5118939b0c4d0ca40f60822f9589f"
+ "shas": "b990bf8d8e2680f56bc1fb39f8f36750ba4ba7fb..f24de0d24746d9f2408eda661698733705bd8a14"
}]
diff --git a/test/corpus/json/javascript/comma-operator.json b/test/corpus/json/javascript/comma-operator.json
index 42e4073be..a814025aa 100644
--- a/test/corpus/json/javascript/comma-operator.json
+++ b/test/corpus/json/javascript/comma-operator.json
@@ -122,9 +122,16 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "a166f0bf388151fe02e1579dd52048ffbac7ba1e",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index e69de29..cff019f 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -0,0 +1 @@",
+ "+a = 1, b = 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b379bb44e39d49ccae9a5a9c09b5341e98525111"
+ "shas": "ac9dba90a6e274a0ed1a230da35e51fd47c0eef4..66691850a16c2c62462cb0e35ddf66f28b75cc35"
}
,{
"testCaseDescription": "javascript-comma-operator-replacement-insert-test",
@@ -553,9 +560,18 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "b379bb44e39d49ccae9a5a9c09b5341e98525111",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index cff019f..93ece10 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1 +1,3 @@",
+ "+c = {d: (3, 4 + 5, 6)};",
+ "+a = 1, b = 2;",
+ " a = 1, b = 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "382a120d7840635acc83e131d4f1dfdfa4f00fe1"
+ "shas": "66691850a16c2c62462cb0e35ddf66f28b75cc35..21ac1ff87f4564dd0b3305f5ad0546472397f93c"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-insert-test",
@@ -1152,9 +1168,19 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "382a120d7840635acc83e131d4f1dfdfa4f00fe1",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index 93ece10..f738c2d 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-c = {d: (3, 4 + 5, 6)};",
+ "+a = 1, b = 2;",
+ " a = 1, b = 2;",
+ " a = 1, b = 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e4bd27a7ee81316dac394d8ef6d591143a4fcdfd"
+ "shas": "21ac1ff87f4564dd0b3305f5ad0546472397f93c..6d5acfbdee3d00d5079694faee05edcccef90c9d"
}
,{
"testCaseDescription": "javascript-comma-operator-replacement-test",
@@ -1751,9 +1777,19 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "e4bd27a7ee81316dac394d8ef6d591143a4fcdfd",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index f738c2d..93ece10 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-a = 1, b = 2;",
+ "+c = {d: (3, 4 + 5, 6)};",
+ " a = 1, b = 2;",
+ " a = 1, b = 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1e20214f0a351a57c164a9cf6cbaaf9af96ea347"
+ "shas": "6d5acfbdee3d00d5079694faee05edcccef90c9d..68b6075b56afa34efaa8020f6edddf07755af8d2"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-replacement-test",
@@ -2300,9 +2336,19 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "1e20214f0a351a57c164a9cf6cbaaf9af96ea347",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index 93ece10..297e28d 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-c = {d: (3, 4 + 5, 6)};",
+ "-a = 1, b = 2;",
+ " a = 1, b = 2;",
+ "+c = {d: (3, 4 + 5, 6)};"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1ea8caf8af9b9fecb2a8c698279d3fb8a459f8f6"
+ "shas": "68b6075b56afa34efaa8020f6edddf07755af8d2..6b6cca519bfa2607fd54303b781add1a23f927a9"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-test",
@@ -2677,9 +2723,17 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "1ea8caf8af9b9fecb2a8c698279d3fb8a459f8f6",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index 297e28d..421bc7f 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1,2 +1 @@",
+ "-a = 1, b = 2;",
+ " c = {d: (3, 4 + 5, 6)};"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d3b8bbae338294db8080ea1cb204cd2e3f18cc8c"
+ "shas": "6b6cca519bfa2607fd54303b781add1a23f927a9..4eb818100f3130330e2fe0f0decb77b827594365"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-rest-test",
@@ -2837,7 +2891,14 @@
"filePaths": [
"comma-operator.js"
],
- "sha1": "d3b8bbae338294db8080ea1cb204cd2e3f18cc8c",
+ "patch": [
+ "diff --git a/comma-operator.js b/comma-operator.js",
+ "index 421bc7f..e69de29 100644",
+ "--- a/comma-operator.js",
+ "+++ b/comma-operator.js",
+ "@@ -1 +0,0 @@",
+ "-c = {d: (3, 4 + 5, 6)};"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9d404dee54cc476fe531b48dc2da5e29a43486bb"
+ "shas": "4eb818100f3130330e2fe0f0decb77b827594365..785493d3bbdebc780e436799269cfe3ecd5bbf77"
}]
diff --git a/test/corpus/json/javascript/comment.json b/test/corpus/json/javascript/comment.json
index 5de70e6b7..31071fd5a 100644
--- a/test/corpus/json/javascript/comment.json
+++ b/test/corpus/json/javascript/comment.json
@@ -65,9 +65,16 @@
"filePaths": [
"comment.js"
],
- "sha1": "817ea011add2e07e6d0d1410269c2882847e4049",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index e69de29..a5821d2 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -0,0 +1 @@",
+ "+// This is a property"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "619e243f35814071c2f33bbb0d97ab91af70a901"
+ "shas": "b7c92617e1bc8e5fbcf483a8ea69e94339a33a4a..cf7c951b9c8ee1023cae2d7a32317a4362912261"
}
,{
"testCaseDescription": "javascript-comment-replacement-insert-test",
@@ -294,9 +301,20 @@
"filePaths": [
"comment.js"
],
- "sha1": "619e243f35814071c2f33bbb0d97ab91af70a901",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index a5821d2..761aa7a 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1 +1,5 @@",
+ "+/*",
+ "+ * This is a method",
+ "+*/",
+ "+// This is a property",
+ " // This is a property"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3963731b56c7bc475cd2de91c4b4e1eec59285f5"
+ "shas": "cf7c951b9c8ee1023cae2d7a32317a4362912261..df64e896d53420fe0c45f73e4a7cd026b432de2c"
}
,{
"testCaseDescription": "javascript-comment-delete-insert-test",
@@ -575,9 +593,21 @@
"filePaths": [
"comment.js"
],
- "sha1": "3963731b56c7bc475cd2de91c4b4e1eec59285f5",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index 761aa7a..3b33406 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1,5 +1,3 @@",
+ "-/*",
+ "- * This is a method",
+ "-*/",
+ "+// This is a property",
+ " // This is a property",
+ " // This is a property"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "05676b7b30c83b8ca42e0522130c5bce57851f0e"
+ "shas": "df64e896d53420fe0c45f73e4a7cd026b432de2c..d66aef0291587fde4d520e86c9f50340aa83dc17"
}
,{
"testCaseDescription": "javascript-comment-replacement-test",
@@ -856,9 +886,21 @@
"filePaths": [
"comment.js"
],
- "sha1": "05676b7b30c83b8ca42e0522130c5bce57851f0e",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index 3b33406..761aa7a 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1,3 +1,5 @@",
+ "-// This is a property",
+ "+/*",
+ "+ * This is a method",
+ "+*/",
+ " // This is a property",
+ " // This is a property"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f3459ba8df488d7752f4f4503dd5f12105a54448"
+ "shas": "d66aef0291587fde4d520e86c9f50340aa83dc17..7f0b4f05b850cba13b1f73b0c3a673c27c41c69f"
}
,{
"testCaseDescription": "javascript-comment-delete-replacement-test",
@@ -1172,9 +1214,21 @@
"filePaths": [
"comment.js"
],
- "sha1": "f3459ba8df488d7752f4f4503dd5f12105a54448",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index 761aa7a..c2a8148 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1,5 +1,4 @@",
+ "+// This is a property",
+ " /*",
+ " * This is a method",
+ " */",
+ "-// This is a property",
+ "-// This is a property"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f188de5837959d937fa5a38725dc0a7005b1be1f"
+ "shas": "7f0b4f05b850cba13b1f73b0c3a673c27c41c69f..7f6aeb575b8b29a59634bee8f9992d33a7326ad5"
}
,{
"testCaseDescription": "javascript-comment-delete-test",
@@ -1422,9 +1476,19 @@
"filePaths": [
"comment.js"
],
- "sha1": "f188de5837959d937fa5a38725dc0a7005b1be1f",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index c2a8148..7c74dcd 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1,4 +1,3 @@",
+ "-// This is a property",
+ " /*",
+ " * This is a method",
+ " */"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9ce9ceadbd1e4cbcb8f1a4bcaf7aa911ed55c166"
+ "shas": "7f6aeb575b8b29a59634bee8f9992d33a7326ad5..e4fd4adee259b94d3c2fd1f48c1b61c2489f6d13"
}
,{
"testCaseDescription": "javascript-comment-delete-rest-test",
@@ -1551,7 +1615,16 @@
"filePaths": [
"comment.js"
],
- "sha1": "9ce9ceadbd1e4cbcb8f1a4bcaf7aa911ed55c166",
+ "patch": [
+ "diff --git a/comment.js b/comment.js",
+ "index 7c74dcd..e69de29 100644",
+ "--- a/comment.js",
+ "+++ b/comment.js",
+ "@@ -1,3 +0,0 @@",
+ "-/*",
+ "- * This is a method",
+ "-*/"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4a90972f24ee5161810f26170784ea8342d7bab5"
+ "shas": "e4fd4adee259b94d3c2fd1f48c1b61c2489f6d13..954df1246c20f230e519c9fb74e256a93cd3e92a"
}]
diff --git a/test/corpus/json/javascript/constructor-call.json b/test/corpus/json/javascript/constructor-call.json
index d5005317b..587d1dd26 100644
--- a/test/corpus/json/javascript/constructor-call.json
+++ b/test/corpus/json/javascript/constructor-call.json
@@ -113,9 +113,16 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "d25c261f3d2c8744d5569a69d8df9e762b5218a4",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index e69de29..9d723b9 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -0,0 +1 @@",
+ "+new module.Klass(1, \"two\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f49e2dbdd5acc2650c0e8cc80cc24b3443efefe4"
+ "shas": "24ed5bdc27489ca788d6784b0385a26f77c8c9d7..2ec18c47ee0949d47e06d4b706051321d7393927"
}
,{
"testCaseDescription": "javascript-constructor-call-replacement-insert-test",
@@ -476,9 +483,18 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "f49e2dbdd5acc2650c0e8cc80cc24b3443efefe4",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index 9d723b9..2c91b11 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1 +1,3 @@",
+ "+new module.Klass(1, \"three\");",
+ "+new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"two\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6bdb8e55055c2a65238f84ea58c766dbeb7cd5c2"
+ "shas": "2ec18c47ee0949d47e06d4b706051321d7393927..1790e7257c8d99f44abc41148a90f83b9a110d2c"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-insert-test",
@@ -987,9 +1003,19 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "6bdb8e55055c2a65238f84ea58c766dbeb7cd5c2",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index 2c91b11..892f542 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-new module.Klass(1, \"three\");",
+ "+new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"two\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8dac85426c13f541f4d5ca0e42f0b2768d2035b2"
+ "shas": "1790e7257c8d99f44abc41148a90f83b9a110d2c..3900103a4bcd12d243d7b2932b5960777b7343e4"
}
,{
"testCaseDescription": "javascript-constructor-call-replacement-test",
@@ -1498,9 +1524,19 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "8dac85426c13f541f4d5ca0e42f0b2768d2035b2",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index 892f542..2c91b11 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-new module.Klass(1, \"two\");",
+ "+new module.Klass(1, \"three\");",
+ " new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"two\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "343290d693162650fb58126c7d03141e779d0cbd"
+ "shas": "3900103a4bcd12d243d7b2932b5960777b7343e4..8eaf061030a44928daec97fca055b3ca51141039"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-replacement-test",
@@ -1938,9 +1974,19 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "343290d693162650fb58126c7d03141e779d0cbd",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index 2c91b11..cd77b98 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1,3 +1,2 @@",
+ "-new module.Klass(1, \"three\");",
+ "-new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"two\");",
+ "+new module.Klass(1, \"three\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5416c94935f0acd8407fd6ae11972256ee0727f4"
+ "shas": "8eaf061030a44928daec97fca055b3ca51141039..ae3ba92f8b0dd27d93e0b5c283f2bd76a3ae217f"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-test",
@@ -2224,9 +2270,17 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "5416c94935f0acd8407fd6ae11972256ee0727f4",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index cd77b98..75f6a29 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1,2 +1 @@",
+ "-new module.Klass(1, \"two\");",
+ " new module.Klass(1, \"three\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ce7d6b9051b87600fe534db4f81bab1cd9776d9c"
+ "shas": "ae3ba92f8b0dd27d93e0b5c283f2bd76a3ae217f..41ff76acb7246669b7453dca3b1cd2d390fbd459"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-rest-test",
@@ -2343,7 +2397,14 @@
"filePaths": [
"constructor-call.js"
],
- "sha1": "ce7d6b9051b87600fe534db4f81bab1cd9776d9c",
+ "patch": [
+ "diff --git a/constructor-call.js b/constructor-call.js",
+ "index 75f6a29..e69de29 100644",
+ "--- a/constructor-call.js",
+ "+++ b/constructor-call.js",
+ "@@ -1 +0,0 @@",
+ "-new module.Klass(1, \"three\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "95e0c499ee3b410bdb68dc5dfdc10f6779f9cc5e"
+ "shas": "41ff76acb7246669b7453dca3b1cd2d390fbd459..349ec3f8639b7b854f6fcfdaaf8e2ef63c05fef7"
}]
diff --git a/test/corpus/json/javascript/delete-operator.json b/test/corpus/json/javascript/delete-operator.json
index 5774a7deb..1863dfeb9 100644
--- a/test/corpus/json/javascript/delete-operator.json
+++ b/test/corpus/json/javascript/delete-operator.json
@@ -99,9 +99,16 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "164de6ef1b42af3022bf42e1fdcab480143b06ef",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index e69de29..c83346d 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -0,0 +1 @@",
+ "+delete thing['prop'];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b888225437f386dca2a30482de1e9cc06c8ed1ed"
+ "shas": "ef3e803a7f48d3ce5e8de0ca9017609664e7ef16..0461e9260a4a5564683fbf96259d64c3562ba580"
}
,{
"testCaseDescription": "javascript-delete-operator-replacement-insert-test",
@@ -406,9 +413,18 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "b888225437f386dca2a30482de1e9cc06c8ed1ed",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index c83346d..7c8b990 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1 +1,3 @@",
+ "+delete thing.prop",
+ "+delete thing['prop'];",
+ " delete thing['prop'];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9d36ec6996e8aa33423dc43df5b5884bc5750742"
+ "shas": "0461e9260a4a5564683fbf96259d64c3562ba580..99c2bc8dc427e20c6fa363fcd86f595bfce7287b"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-insert-test",
@@ -833,9 +849,19 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "9d36ec6996e8aa33423dc43df5b5884bc5750742",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index 7c8b990..f506e36 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-delete thing.prop",
+ "+delete thing['prop'];",
+ " delete thing['prop'];",
+ " delete thing['prop'];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e4c386ff7cf5914e3d03a1b4e10416115d11766c"
+ "shas": "99c2bc8dc427e20c6fa363fcd86f595bfce7287b..afb58bf5ef29de81c83d85b695c637a78769f7c4"
}
,{
"testCaseDescription": "javascript-delete-operator-replacement-test",
@@ -1260,9 +1286,19 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "e4c386ff7cf5914e3d03a1b4e10416115d11766c",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index f506e36..7c8b990 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-delete thing['prop'];",
+ "+delete thing.prop",
+ " delete thing['prop'];",
+ " delete thing['prop'];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "43a3be746ece5fa2650750d060c63295fc15c27b"
+ "shas": "afb58bf5ef29de81c83d85b695c637a78769f7c4..380a9c46ee9372e02905f51f67580c6eaaa6c1c3"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-replacement-test",
@@ -1630,9 +1666,19 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "43a3be746ece5fa2650750d060c63295fc15c27b",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index 7c8b990..2dfe079 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-delete thing.prop",
+ "-delete thing['prop'];",
+ " delete thing['prop'];",
+ "+delete thing.prop"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "56ee50869ff5102e8aa3bff067886ac95e5c2da6"
+ "shas": "380a9c46ee9372e02905f51f67580c6eaaa6c1c3..4ba8af8d818542e86d02544a1b80c6301f7a89ea"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-test",
@@ -1874,9 +1920,17 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "56ee50869ff5102e8aa3bff067886ac95e5c2da6",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index 2dfe079..9d68dfb 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1,2 +1 @@",
+ "-delete thing['prop'];",
+ " delete thing.prop"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "be8ba365ed1831c473fc55c8d73cc3b8693c68b6"
+ "shas": "4ba8af8d818542e86d02544a1b80c6301f7a89ea..ce4b96be08657c97d2afe1c5a0604685d81cf378"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-rest-test",
@@ -1979,7 +2033,14 @@
"filePaths": [
"delete-operator.js"
],
- "sha1": "be8ba365ed1831c473fc55c8d73cc3b8693c68b6",
+ "patch": [
+ "diff --git a/delete-operator.js b/delete-operator.js",
+ "index 9d68dfb..e69de29 100644",
+ "--- a/delete-operator.js",
+ "+++ b/delete-operator.js",
+ "@@ -1 +0,0 @@",
+ "-delete thing.prop"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "01c8f3bc964827b93c4f234df17d50755ab361c2"
+ "shas": "ce4b96be08657c97d2afe1c5a0604685d81cf378..5434e42ccac5d681cef511be2131960ba1884c93"
}]
diff --git a/test/corpus/json/javascript/do-while-statement.json b/test/corpus/json/javascript/do-while-statement.json
index 87dbd06e7..8f6ae824b 100644
--- a/test/corpus/json/javascript/do-while-statement.json
+++ b/test/corpus/json/javascript/do-while-statement.json
@@ -122,9 +122,16 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "c83c4ea2ff4d29ff6ac3b44972b1e00a723d97b3",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index e69de29..d1ec804 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -0,0 +1 @@",
+ "+do { console.log(insert); } while (true);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "af1d1633876ccf466f04130c8cd49fd2c52b4d22"
+ "shas": "a22f0481bc6a70fba4f09d450abc7b2787f85762..7abcf89b7a75b91d70522e0d5aa9b9307ef26224"
}
,{
"testCaseDescription": "javascript-do-while-statement-replacement-insert-test",
@@ -521,9 +528,18 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "af1d1633876ccf466f04130c8cd49fd2c52b4d22",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index d1ec804..d9a410d 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1 +1,3 @@",
+ "+do { console.log(replacement); } while (false);",
+ "+do { console.log(insert); } while (true);",
+ " do { console.log(insert); } while (true);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d11b5b96239502cdf848ef74bb73370576491d13"
+ "shas": "7abcf89b7a75b91d70522e0d5aa9b9307ef26224..74d2541a79d1212236c1d9f7a9dd5138a5dcf059"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-insert-test",
@@ -1088,9 +1104,19 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "d11b5b96239502cdf848ef74bb73370576491d13",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index d9a410d..4197835 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-do { console.log(replacement); } while (false);",
+ "+do { console.log(insert); } while (true);",
+ " do { console.log(insert); } while (true);",
+ " do { console.log(insert); } while (true);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d1d0b7120f9726cd476553c1a1c2b5ddca04c521"
+ "shas": "74d2541a79d1212236c1d9f7a9dd5138a5dcf059..8133ce7720b56dceb36f7fd781e37f3348c7a72f"
}
,{
"testCaseDescription": "javascript-do-while-statement-replacement-test",
@@ -1655,9 +1681,19 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "d1d0b7120f9726cd476553c1a1c2b5ddca04c521",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index 4197835..d9a410d 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-do { console.log(insert); } while (true);",
+ "+do { console.log(replacement); } while (false);",
+ " do { console.log(insert); } while (true);",
+ " do { console.log(insert); } while (true);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "67888b81e91c4897b05926958fc4a23dabc8abb3"
+ "shas": "8133ce7720b56dceb36f7fd781e37f3348c7a72f..c6c0469d03dd8958d0e0ad486cdd788101104fa7"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-replacement-test",
@@ -2140,9 +2176,19 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "67888b81e91c4897b05926958fc4a23dabc8abb3",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index d9a410d..c5291b4 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-do { console.log(replacement); } while (false);",
+ "-do { console.log(insert); } while (true);",
+ " do { console.log(insert); } while (true);",
+ "+do { console.log(replacement); } while (false);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "33feb8da4ca201879b08b09989b6927d23655373"
+ "shas": "c6c0469d03dd8958d0e0ad486cdd788101104fa7..3b1ba172e86f43f1976164c806df448a6bc53e3e"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-test",
@@ -2453,9 +2499,17 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "33feb8da4ca201879b08b09989b6927d23655373",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index c5291b4..6085cb1 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1,2 +1 @@",
+ "-do { console.log(insert); } while (true);",
+ " do { console.log(replacement); } while (false);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "19fd6aee4cfff87e8754770c5fd7af14ea2eb279"
+ "shas": "3b1ba172e86f43f1976164c806df448a6bc53e3e..cb580d744365fee8ee88e2dcc525cd7af8b237fc"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-rest-test",
@@ -2581,7 +2635,14 @@
"filePaths": [
"do-while-statement.js"
],
- "sha1": "19fd6aee4cfff87e8754770c5fd7af14ea2eb279",
+ "patch": [
+ "diff --git a/do-while-statement.js b/do-while-statement.js",
+ "index 6085cb1..e69de29 100644",
+ "--- a/do-while-statement.js",
+ "+++ b/do-while-statement.js",
+ "@@ -1 +0,0 @@",
+ "-do { console.log(replacement); } while (false);"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c26d48032e032fd0fc1650e48cee5545f6337902"
+ "shas": "cb580d744365fee8ee88e2dcc525cd7af8b237fc..9fdae081cef5395f539eef79836a911574344379"
}]
diff --git a/test/corpus/json/javascript/export.json b/test/corpus/json/javascript/export.json
index a5133e4a6..b95c0f0f1 100644
--- a/test/corpus/json/javascript/export.json
+++ b/test/corpus/json/javascript/export.json
@@ -847,9 +847,26 @@
"filePaths": [
"export.js"
],
- "sha1": "22db42187b94dca9b3ba3ce80361c21a8b48b777",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index e69de29..dcd9320 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -0,0 +1,11 @@",
+ "+export { name1, name2, name3, nameN };",
+ "+export { variable1 as name1, variable2 as name2, nameN };",
+ "+export let name1, name2, nameN;",
+ "+export let name1 = value1, name2 = value2, name3, nameN;",
+ "+export default namedFunction;",
+ "+export default function () { };",
+ "+export default function name1() { };",
+ "+export { name1 as default };",
+ "+export * from 'foo';",
+ "+export { name1, name2, nameN } from 'foo';",
+ "+export { import1 as name1, import2 as name2, nameN } from 'bar';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "69fafd1cab17e5f7d23b70e090674ca58927dfe6"
+ "shas": "0bb74af8eede739c6d9a6b79a13e61263d3c52e6..3d34a0f856d545b0a728805cb18bb843d66b31ef"
}
,{
"testCaseDescription": "javascript-export-replacement-insert-test",
@@ -4106,9 +4123,40 @@
"filePaths": [
"export.js"
],
- "sha1": "69fafd1cab17e5f7d23b70e090674ca58927dfe6",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index dcd9320..c8b53ff 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,3 +1,25 @@",
+ "+export { name4, name5, name6, nameZ };",
+ "+export { variable2 as name2, variable3 as name3, nameY };",
+ "+export let name3, name4, nameT;",
+ "+export let name2 = value2, name3 = value3, name4, nameO;",
+ "+export default otherNamedFunction;",
+ "+export default function newName1() {};",
+ "+export default function () {};",
+ "+export { name2 as statement };",
+ "+export * from 'baz';",
+ "+export { name7, name8, nameP } from 'buzz';",
+ "+export { import6 as name6, import7 as name7, nameB } from 'fizz';",
+ "+export { name1, name2, name3, nameN };",
+ "+export { variable1 as name1, variable2 as name2, nameN };",
+ "+export let name1, name2, nameN;",
+ "+export let name1 = value1, name2 = value2, name3, nameN;",
+ "+export default namedFunction;",
+ "+export default function () { };",
+ "+export default function name1() { };",
+ "+export { name1 as default };",
+ "+export * from 'foo';",
+ "+export { name1, name2, nameN } from 'foo';",
+ "+export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ " export { name1, name2, name3, nameN };",
+ " export { variable1 as name1, variable2 as name2, nameN };",
+ " export let name1, name2, nameN;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b7fa303ae2482bd012db32fc154762310dad6990"
+ "shas": "3d34a0f856d545b0a728805cb18bb843d66b31ef..14555cd2f315cd841f9d581c0dda879f1f3d2dd7"
}
,{
"testCaseDescription": "javascript-export-delete-insert-test",
@@ -8961,9 +9009,40 @@
"filePaths": [
"export.js"
],
- "sha1": "b7fa303ae2482bd012db32fc154762310dad6990",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index c8b53ff..ad3f21a 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,14 +1,14 @@",
+ "-export { name4, name5, name6, nameZ };",
+ "-export { variable2 as name2, variable3 as name3, nameY };",
+ "-export let name3, name4, nameT;",
+ "-export let name2 = value2, name3 = value3, name4, nameO;",
+ "-export default otherNamedFunction;",
+ "-export default function newName1() {};",
+ "-export default function () {};",
+ "-export { name2 as statement };",
+ "-export * from 'baz';",
+ "-export { name7, name8, nameP } from 'buzz';",
+ "-export { import6 as name6, import7 as name7, nameB } from 'fizz';",
+ "+export { name1, name2, name3, nameN };",
+ "+export { variable1 as name1, variable2 as name2, nameN };",
+ "+export let name1, name2, nameN;",
+ "+export let name1 = value1, name2 = value2, name3, nameN;",
+ "+export default namedFunction;",
+ "+export default function () { };",
+ "+export default function name1() { };",
+ "+export { name1 as default };",
+ "+export * from 'foo';",
+ "+export { name1, name2, nameN } from 'foo';",
+ "+export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ " export { name1, name2, name3, nameN };",
+ " export { variable1 as name1, variable2 as name2, nameN };",
+ " export let name1, name2, nameN;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fc212964303910e919462077da89963cdb1be98d"
+ "shas": "14555cd2f315cd841f9d581c0dda879f1f3d2dd7..db45ffdca40149b2a8ab65cef948169930779ced"
}
,{
"testCaseDescription": "javascript-export-replacement-test",
@@ -13802,9 +13881,40 @@
"filePaths": [
"export.js"
],
- "sha1": "fc212964303910e919462077da89963cdb1be98d",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index ad3f21a..c8b53ff 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,14 +1,14 @@",
+ "-export { name1, name2, name3, nameN };",
+ "-export { variable1 as name1, variable2 as name2, nameN };",
+ "-export let name1, name2, nameN;",
+ "-export let name1 = value1, name2 = value2, name3, nameN;",
+ "-export default namedFunction;",
+ "-export default function () { };",
+ "-export default function name1() { };",
+ "-export { name1 as default };",
+ "-export * from 'foo';",
+ "-export { name1, name2, nameN } from 'foo';",
+ "-export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ "+export { name4, name5, name6, nameZ };",
+ "+export { variable2 as name2, variable3 as name3, nameY };",
+ "+export let name3, name4, nameT;",
+ "+export let name2 = value2, name3 = value3, name4, nameO;",
+ "+export default otherNamedFunction;",
+ "+export default function newName1() {};",
+ "+export default function () {};",
+ "+export { name2 as statement };",
+ "+export * from 'baz';",
+ "+export { name7, name8, nameP } from 'buzz';",
+ "+export { import6 as name6, import7 as name7, nameB } from 'fizz';",
+ " export { name1, name2, name3, nameN };",
+ " export { variable1 as name1, variable2 as name2, nameN };",
+ " export let name1, name2, nameN;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1b524fb912fc311ad4e96593ecfdb594e148f97d"
+ "shas": "db45ffdca40149b2a8ab65cef948169930779ced..a7d8a8c67df112242870b85873789fcd84c93dc4"
}
,{
"testCaseDescription": "javascript-export-delete-replacement-test",
@@ -17872,9 +17982,55 @@
"filePaths": [
"export.js"
],
- "sha1": "1b524fb912fc311ad4e96593ecfdb594e148f97d",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index c8b53ff..281c672 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,25 +1,3 @@",
+ "-export { name4, name5, name6, nameZ };",
+ "-export { variable2 as name2, variable3 as name3, nameY };",
+ "-export let name3, name4, nameT;",
+ "-export let name2 = value2, name3 = value3, name4, nameO;",
+ "-export default otherNamedFunction;",
+ "-export default function newName1() {};",
+ "-export default function () {};",
+ "-export { name2 as statement };",
+ "-export * from 'baz';",
+ "-export { name7, name8, nameP } from 'buzz';",
+ "-export { import6 as name6, import7 as name7, nameB } from 'fizz';",
+ "-export { name1, name2, name3, nameN };",
+ "-export { variable1 as name1, variable2 as name2, nameN };",
+ "-export let name1, name2, nameN;",
+ "-export let name1 = value1, name2 = value2, name3, nameN;",
+ "-export default namedFunction;",
+ "-export default function () { };",
+ "-export default function name1() { };",
+ "-export { name1 as default };",
+ "-export * from 'foo';",
+ "-export { name1, name2, nameN } from 'foo';",
+ "-export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ " export { name1, name2, name3, nameN };",
+ " export { variable1 as name1, variable2 as name2, nameN };",
+ " export let name1, name2, nameN;",
+ "@@ -31,3 +9,14 @@ export { name1 as default };",
+ " export * from 'foo';",
+ " export { name1, name2, nameN } from 'foo';",
+ " export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ "+export { name4, name5, name6, nameZ };",
+ "+export { variable2 as name2, variable3 as name3, nameY };",
+ "+export let name3, name4, nameT;",
+ "+export let name2 = value2, name3 = value3, name4, nameO;",
+ "+export default otherNamedFunction;",
+ "+export default function newName1() {};",
+ "+export default function () {};",
+ "+export { name2 as statement };",
+ "+export * from 'baz';",
+ "+export { name7, name8, nameP } from 'buzz';",
+ "+export { import6 as name6, import7 as name7, nameB } from 'fizz';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3032a50afea32bd74ade9b5ddec65057e73841b4"
+ "shas": "a7d8a8c67df112242870b85873789fcd84c93dc4..33d58d61e860aaf9d71c3a00aff457cf8c5e7d15"
}
,{
"testCaseDescription": "javascript-export-delete-test",
@@ -20320,9 +20476,29 @@
"filePaths": [
"export.js"
],
- "sha1": "3032a50afea32bd74ade9b5ddec65057e73841b4",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index 281c672..e105ba7 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,14 +1,3 @@",
+ "-export { name1, name2, name3, nameN };",
+ "-export { variable1 as name1, variable2 as name2, nameN };",
+ "-export let name1, name2, nameN;",
+ "-export let name1 = value1, name2 = value2, name3, nameN;",
+ "-export default namedFunction;",
+ "-export default function () { };",
+ "-export default function name1() { };",
+ "-export { name1 as default };",
+ "-export * from 'foo';",
+ "-export { name1, name2, nameN } from 'foo';",
+ "-export { import1 as name1, import2 as name2, nameN } from 'bar';",
+ " export { name4, name5, name6, nameZ };",
+ " export { variable2 as name2, variable3 as name3, nameY };",
+ " export let name3, name4, nameT;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d76dce2c810aa0215d1bdb63be6fa2a59e65f5dd"
+ "shas": "33d58d61e860aaf9d71c3a00aff457cf8c5e7d15..52b3a9b592646247d5884c136733a12cb2971479"
}
,{
"testCaseDescription": "javascript-export-delete-rest-test",
@@ -21173,7 +21349,24 @@
"filePaths": [
"export.js"
],
- "sha1": "d76dce2c810aa0215d1bdb63be6fa2a59e65f5dd",
+ "patch": [
+ "diff --git a/export.js b/export.js",
+ "index e105ba7..e69de29 100644",
+ "--- a/export.js",
+ "+++ b/export.js",
+ "@@ -1,11 +0,0 @@",
+ "-export { name4, name5, name6, nameZ };",
+ "-export { variable2 as name2, variable3 as name3, nameY };",
+ "-export let name3, name4, nameT;",
+ "-export let name2 = value2, name3 = value3, name4, nameO;",
+ "-export default otherNamedFunction;",
+ "-export default function newName1() {};",
+ "-export default function () {};",
+ "-export { name2 as statement };",
+ "-export * from 'baz';",
+ "-export { name7, name8, nameP } from 'buzz';",
+ "-export { import6 as name6, import7 as name7, nameB } from 'fizz';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9b877906e9b09b14f277f4c3058dfc04eca3d222"
+ "shas": "52b3a9b592646247d5884c136733a12cb2971479..5dede241573c8e353a4d8c662194e8e3b750e01a"
}]
diff --git a/test/corpus/json/javascript/false.json b/test/corpus/json/javascript/false.json
index 52c1f4d00..3fa10e9de 100644
--- a/test/corpus/json/javascript/false.json
+++ b/test/corpus/json/javascript/false.json
@@ -74,9 +74,16 @@
"filePaths": [
"false.js"
],
- "sha1": "2969c3538fa44b0b9930417f37b669ad53801cd1",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index e69de29..8a63946 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -0,0 +1 @@",
+ "+false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "095c3902a688889958d23a03d630c67d22698541"
+ "shas": "163b832af7eb86fe2d319810d137565e70a924f4..534e91d885497e33f825d5c9e7e90ef4986e83b6"
}
,{
"testCaseDescription": "javascript-false-replacement-insert-test",
@@ -281,9 +288,18 @@
"filePaths": [
"false.js"
],
- "sha1": "095c3902a688889958d23a03d630c67d22698541",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 8a63946..86574b1 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1 +1,3 @@",
+ "+return false;",
+ "+false;",
+ " false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b58497ea325bb4126bcb61842f0625cce094c3b3"
+ "shas": "534e91d885497e33f825d5c9e7e90ef4986e83b6..f57bd598b66633b00684cbdb1b4d9ee81148d197"
}
,{
"testCaseDescription": "javascript-false-delete-insert-test",
@@ -560,9 +576,19 @@
"filePaths": [
"false.js"
],
- "sha1": "b58497ea325bb4126bcb61842f0625cce094c3b3",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 86574b1..7bae7c5 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1,3 +1,3 @@",
+ "-return false;",
+ "+false;",
+ " false;",
+ " false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c8576e58f77b78a88ef4a2c7c5e4359988262dcb"
+ "shas": "f57bd598b66633b00684cbdb1b4d9ee81148d197..09585d310062f9fe315c2a400c69cb13cf67675a"
}
,{
"testCaseDescription": "javascript-false-replacement-test",
@@ -839,9 +865,19 @@
"filePaths": [
"false.js"
],
- "sha1": "c8576e58f77b78a88ef4a2c7c5e4359988262dcb",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 7bae7c5..86574b1 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1,3 +1,3 @@",
+ "-false;",
+ "+return false;",
+ " false;",
+ " false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6097785f86a891c394346a254baa66d68379a6e9"
+ "shas": "09585d310062f9fe315c2a400c69cb13cf67675a..ed00e5f614db396d4d52c2bacefb89580ad7fbba"
}
,{
"testCaseDescription": "javascript-false-delete-replacement-test",
@@ -1084,9 +1120,19 @@
"filePaths": [
"false.js"
],
- "sha1": "6097785f86a891c394346a254baa66d68379a6e9",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 86574b1..85b5be9 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1,3 +1,2 @@",
+ "-return false;",
+ "-false;",
+ " false;",
+ "+return false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e00f9f0164fc3e41fe973b3c0ea6b24d43a22eca"
+ "shas": "ed00e5f614db396d4d52c2bacefb89580ad7fbba..d8c0287cc65dc125d283d6aa0e6cd32a3d5e1e31"
}
,{
"testCaseDescription": "javascript-false-delete-test",
@@ -1253,9 +1299,17 @@
"filePaths": [
"false.js"
],
- "sha1": "e00f9f0164fc3e41fe973b3c0ea6b24d43a22eca",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 85b5be9..1f328b3 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1,2 +1 @@",
+ "-false;",
+ " return false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2e5600ef22e895d75944c1b0b428703529387b3f"
+ "shas": "d8c0287cc65dc125d283d6aa0e6cd32a3d5e1e31..cd36fb39c2618d389cd4fd7511eded4aa0bdccf2"
}
,{
"testCaseDescription": "javascript-false-delete-rest-test",
@@ -1333,7 +1387,14 @@
"filePaths": [
"false.js"
],
- "sha1": "2e5600ef22e895d75944c1b0b428703529387b3f",
+ "patch": [
+ "diff --git a/false.js b/false.js",
+ "index 1f328b3..e69de29 100644",
+ "--- a/false.js",
+ "+++ b/false.js",
+ "@@ -1 +0,0 @@",
+ "-return false;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2f777027985687b45cb77235606c630008823245"
+ "shas": "cd36fb39c2618d389cd4fd7511eded4aa0bdccf2..025ac2dcb7ae8e622fb5a7f0508e2ec9e15604f8"
}]
diff --git a/test/corpus/json/javascript/for-in-statement.json b/test/corpus/json/javascript/for-in-statement.json
index 389172f7b..5cd87ed3a 100644
--- a/test/corpus/json/javascript/for-in-statement.json
+++ b/test/corpus/json/javascript/for-in-statement.json
@@ -115,9 +115,16 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "f23716f158172021ba81a7189a8e49480c956764",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index e69de29..f928287 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -0,0 +1 @@",
+ "+for (thing in things) { thing(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "06057b302b4cd3a2dfe0cf57abaf6e240188e573"
+ "shas": "52f50b42f461e7840a4f2f57f62530561ab97768..d9d09d76031e48a29cbb2b4bd6ac915db7faf669"
}
,{
"testCaseDescription": "javascript-for-in-statement-replacement-insert-test",
@@ -486,9 +493,18 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "06057b302b4cd3a2dfe0cf57abaf6e240188e573",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index f928287..4a482e9 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1 +1,3 @@",
+ "+for (item in items) { item(); }",
+ "+for (thing in things) { thing(); }",
+ " for (thing in things) { thing(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "12e9d054fe870945f9a61b9e666f680710af3b4b"
+ "shas": "d9d09d76031e48a29cbb2b4bd6ac915db7faf669..7a879f58e1b410f3863c826bb925b05cb7473957"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-insert-test",
@@ -1013,9 +1029,19 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "12e9d054fe870945f9a61b9e666f680710af3b4b",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index 4a482e9..e949baf 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (item in items) { item(); }",
+ "+for (thing in things) { thing(); }",
+ " for (thing in things) { thing(); }",
+ " for (thing in things) { thing(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6e1078ede2f32a64ce03241108779bfaabc2117b"
+ "shas": "7a879f58e1b410f3863c826bb925b05cb7473957..67b08f6c17669e3f8340b3ac65173960a248bb4b"
}
,{
"testCaseDescription": "javascript-for-in-statement-replacement-test",
@@ -1540,9 +1566,19 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "6e1078ede2f32a64ce03241108779bfaabc2117b",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index e949baf..4a482e9 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (thing in things) { thing(); }",
+ "+for (item in items) { item(); }",
+ " for (thing in things) { thing(); }",
+ " for (thing in things) { thing(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "450b2cf8853523373b68a274fed38b82dd65ed37"
+ "shas": "67b08f6c17669e3f8340b3ac65173960a248bb4b..fd3d006a8e9e4c4d7d89911c4bf9d52271d6bfc5"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-replacement-test",
@@ -1990,9 +2026,19 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "450b2cf8853523373b68a274fed38b82dd65ed37",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index 4a482e9..6b5f12a 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-for (item in items) { item(); }",
+ "-for (thing in things) { thing(); }",
+ " for (thing in things) { thing(); }",
+ "+for (item in items) { item(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "dd652ef7b12414e79097fc6135dc0a3d8e3daf4b"
+ "shas": "fd3d006a8e9e4c4d7d89911c4bf9d52271d6bfc5..6c112e115ba5ab522314b492040a7e80499a9933"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-test",
@@ -2282,9 +2328,17 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "dd652ef7b12414e79097fc6135dc0a3d8e3daf4b",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index 6b5f12a..a3d8882 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1,2 +1 @@",
+ "-for (thing in things) { thing(); }",
+ " for (item in items) { item(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d75c99e6e8fdbf0035c7eff75e30481a34567f6f"
+ "shas": "6c112e115ba5ab522314b492040a7e80499a9933..11445e23388ee5f53f07b1df875ecb65f30beafc"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-rest-test",
@@ -2403,7 +2457,14 @@
"filePaths": [
"for-in-statement.js"
],
- "sha1": "d75c99e6e8fdbf0035c7eff75e30481a34567f6f",
+ "patch": [
+ "diff --git a/for-in-statement.js b/for-in-statement.js",
+ "index a3d8882..e69de29 100644",
+ "--- a/for-in-statement.js",
+ "+++ b/for-in-statement.js",
+ "@@ -1 +0,0 @@",
+ "-for (item in items) { item(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4993de9ab311936d640089fb8e5490f393d0e49d"
+ "shas": "11445e23388ee5f53f07b1df875ecb65f30beafc..790f317cf635d64f5798d63a5b58483fd6bad99f"
}]
diff --git a/test/corpus/json/javascript/for-loop-with-in-statement.json b/test/corpus/json/javascript/for-loop-with-in-statement.json
index 9ab6c739e..12c6a7aa5 100644
--- a/test/corpus/json/javascript/for-loop-with-in-statement.json
+++ b/test/corpus/json/javascript/for-loop-with-in-statement.json
@@ -195,9 +195,16 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "8f8309aab5b170620dd56a95dde3a0a1c4307c68",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index e69de29..c467478 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -0,0 +1 @@",
+ "+for (key in something && i = 0; i < n; i++) { doSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d4ef819b2032599dec76b1b8bca7a958bb532a7d"
+ "shas": "8dd4d424eeae076b657c04fb290058c4635ae818..9811288bc6b350e349973dec14748a359efedc76"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test",
@@ -886,9 +893,18 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "d4ef819b2032599dec76b1b8bca7a958bb532a7d",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index c467478..0147d31 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1 +1,3 @@",
+ "+for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
+ "+for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "49650dfb0ab5263272659bbda9ff3973d87b27ba"
+ "shas": "9811288bc6b350e349973dec14748a359efedc76..63fc9f47c0b135eec17ac28e315a58a052f21fc8"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test",
@@ -1891,9 +1907,19 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "49650dfb0ab5263272659bbda9ff3973d87b27ba",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index 0147d31..306fa88 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
+ "+for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "22e9c180fbf1f60eb4100fa046df08f30da91ed0"
+ "shas": "63fc9f47c0b135eec17ac28e315a58a052f21fc8..2cd005d0e852939bc0e1af4e0de6d3fba1855845"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test",
@@ -2896,9 +2922,19 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "22e9c180fbf1f60eb4100fa046df08f30da91ed0",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index 306fa88..0147d31 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ "+for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c0ffef38d1db59a8c01b722f43ff51088d0d5aab"
+ "shas": "2cd005d0e852939bc0e1af4e0de6d3fba1855845..a0f7c8fd3b681499414c0eb241efb7d677d12d93"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test",
@@ -3746,9 +3782,19 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "c0ffef38d1db59a8c01b722f43ff51088d0d5aab",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index 0147d31..f23fa31 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
+ "-for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ "+for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3ffd2138c6d5f249ff6546a3be3b2f05964872bc"
+ "shas": "a0f7c8fd3b681499414c0eb241efb7d677d12d93..6b7a2fd51ee8f4d50b6694c613e614f365ae5043"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-test",
@@ -4278,9 +4324,17 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "3ffd2138c6d5f249ff6546a3be3b2f05964872bc",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index f23fa31..e968160 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1,2 +1 @@",
+ "-for (key in something && i = 0; i < n; i++) { doSomething(); }",
+ " for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e8052ac71b7500d674a59d99771f30d9ada7d3a8"
+ "shas": "6b7a2fd51ee8f4d50b6694c613e614f365ae5043..1ae61c25b593a57731d6b465c56186922d43a9be"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test",
@@ -4479,7 +4533,14 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
- "sha1": "e8052ac71b7500d674a59d99771f30d9ada7d3a8",
+ "patch": [
+ "diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
+ "index e968160..e69de29 100644",
+ "--- a/for-loop-with-in-statement.js",
+ "+++ b/for-loop-with-in-statement.js",
+ "@@ -1 +0,0 @@",
+ "-for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ceb4421fb8736b7ea77887631c5d741c11d4b91c"
+ "shas": "1ae61c25b593a57731d6b465c56186922d43a9be..d86b209de9dedc4b2f245fbfc5ea1497b4f94189"
}]
diff --git a/test/corpus/json/javascript/for-of-statement.json b/test/corpus/json/javascript/for-of-statement.json
index f971320f9..e28c116e8 100644
--- a/test/corpus/json/javascript/for-of-statement.json
+++ b/test/corpus/json/javascript/for-of-statement.json
@@ -122,9 +122,16 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "ceb4421fb8736b7ea77887631c5d741c11d4b91c",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index e69de29..1ed2754 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -0,0 +1 @@",
+ "+for (let item of items) { process(item); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0c9335f886a0202dc30976538d51dfb57c7ae520"
+ "shas": "d86b209de9dedc4b2f245fbfc5ea1497b4f94189..692134aa403abb6b6144648a7fdae4867d7a6f24"
}
,{
"testCaseDescription": "javascript-for-of-statement-replacement-insert-test",
@@ -521,9 +528,18 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "0c9335f886a0202dc30976538d51dfb57c7ae520",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index 1ed2754..ab20ded 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1 +1,3 @@",
+ "+for (let thing of things) { process(thing); };",
+ "+for (let item of items) { process(item); };",
+ " for (let item of items) { process(item); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "932ae5f0d12f4769effc524c3177feab8b966414"
+ "shas": "692134aa403abb6b6144648a7fdae4867d7a6f24..59fdc2a48434656b3b264103f12ec958666dd913"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-insert-test",
@@ -1090,9 +1106,19 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "932ae5f0d12f4769effc524c3177feab8b966414",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index ab20ded..19561a3 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (let thing of things) { process(thing); };",
+ "+for (let item of items) { process(item); };",
+ " for (let item of items) { process(item); };",
+ " for (let item of items) { process(item); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a4b5fe78be9d693b83c211656682bc96f53f6aed"
+ "shas": "59fdc2a48434656b3b264103f12ec958666dd913..34c9a61a59c6337de1d9f3dd811b6d2d7fb227e4"
}
,{
"testCaseDescription": "javascript-for-of-statement-replacement-test",
@@ -1659,9 +1685,19 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "a4b5fe78be9d693b83c211656682bc96f53f6aed",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index 19561a3..ab20ded 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (let item of items) { process(item); };",
+ "+for (let thing of things) { process(thing); };",
+ " for (let item of items) { process(item); };",
+ " for (let item of items) { process(item); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e80000137337b938b395c8893c6d4deac64878ec"
+ "shas": "34c9a61a59c6337de1d9f3dd811b6d2d7fb227e4..38d929287ed0d1fba0a0472cb2867bc8a36ed9f3"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-replacement-test",
@@ -2144,9 +2180,19 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "e80000137337b938b395c8893c6d4deac64878ec",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index ab20ded..62db34f 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-for (let thing of things) { process(thing); };",
+ "-for (let item of items) { process(item); };",
+ " for (let item of items) { process(item); };",
+ "+for (let thing of things) { process(thing); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "feaa1e11e598b939a5801083fd26fff28dc088e3"
+ "shas": "38d929287ed0d1fba0a0472cb2867bc8a36ed9f3..7be620405c8ed9315f8d781a4e0f70af4ddf7661"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-test",
@@ -2457,9 +2503,17 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "feaa1e11e598b939a5801083fd26fff28dc088e3",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index 62db34f..5170ce4 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1,2 +1 @@",
+ "-for (let item of items) { process(item); };",
+ " for (let thing of things) { process(thing); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fa7431f18dfe698422b41da804063d35615f83d3"
+ "shas": "7be620405c8ed9315f8d781a4e0f70af4ddf7661..0b04e915606b848351ed5a2a6d7cbd1b17dd624d"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-rest-test",
@@ -2585,7 +2639,14 @@
"filePaths": [
"for-of-statement.js"
],
- "sha1": "fa7431f18dfe698422b41da804063d35615f83d3",
+ "patch": [
+ "diff --git a/for-of-statement.js b/for-of-statement.js",
+ "index 5170ce4..e69de29 100644",
+ "--- a/for-of-statement.js",
+ "+++ b/for-of-statement.js",
+ "@@ -1 +0,0 @@",
+ "-for (let thing of things) { process(thing); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0fb01413d57a0e85053f498b1e91effda758d625"
+ "shas": "0b04e915606b848351ed5a2a6d7cbd1b17dd624d..02fd2e5dc8f8de3c7dfdb7fc35ffa79ecc5a9711"
}]
diff --git a/test/corpus/json/javascript/for-statement.json b/test/corpus/json/javascript/for-statement.json
index a67184765..41870c942 100644
--- a/test/corpus/json/javascript/for-statement.json
+++ b/test/corpus/json/javascript/for-statement.json
@@ -186,9 +186,16 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "f6f1a76087498759b09a64e05a2d7c1867a77ff3",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index e69de29..2f51258 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -0,0 +1 @@",
+ "+for (i = 0, init(); i < 10; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8bff77a0d6b6f54aabc11ed858a61a21588c0b55"
+ "shas": "6ca5e77d4063360bcd0a90d891c3e81e09835b84..67d8ed44c8d2d20d1e580881d6c0700961468d34"
}
,{
"testCaseDescription": "javascript-for-statement-replacement-insert-test",
@@ -841,9 +848,18 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "8bff77a0d6b6f54aabc11ed858a61a21588c0b55",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index 2f51258..095241f 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1 +1,3 @@",
+ "+for (i = 0, init(); i < 100; i++) { log(i); }",
+ "+for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f86f43f8811bcbf4210981cf2f6457d775da3c6c"
+ "shas": "67d8ed44c8d2d20d1e580881d6c0700961468d34..b2b93708ee067b6893c94f3728896489a9ac3c4a"
}
,{
"testCaseDescription": "javascript-for-statement-delete-insert-test",
@@ -1790,9 +1806,19 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "f86f43f8811bcbf4210981cf2f6457d775da3c6c",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index 095241f..9b0e26d 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (i = 0, init(); i < 100; i++) { log(i); }",
+ "+for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d5fb28436455d42b065a2cec4fbd687af6fd830d"
+ "shas": "b2b93708ee067b6893c94f3728896489a9ac3c4a..f4c615d37eccfcad119e8743f398fe72f12e2119"
}
,{
"testCaseDescription": "javascript-for-statement-replacement-test",
@@ -2739,9 +2765,19 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "d5fb28436455d42b065a2cec4fbd687af6fd830d",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index 9b0e26d..095241f 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-for (i = 0, init(); i < 10; i++) { log(i); }",
+ "+for (i = 0, init(); i < 100; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fa7723628489db5130dbad6152125d10dfbf9e1f"
+ "shas": "f4c615d37eccfcad119e8743f398fe72f12e2119..e7c088c711503cc6f52aa3307363dd069ef73101"
}
,{
"testCaseDescription": "javascript-for-statement-delete-replacement-test",
@@ -3544,9 +3580,19 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "fa7723628489db5130dbad6152125d10dfbf9e1f",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index 095241f..39af699 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-for (i = 0, init(); i < 100; i++) { log(i); }",
+ "-for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 10; i++) { log(i); }",
+ "+for (i = 0, init(); i < 100; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0267f05f5b16c04fc84af196f688f8f2d1962654"
+ "shas": "e7c088c711503cc6f52aa3307363dd069ef73101..030f6e47ed5f03b21e98c128d8bb398225366bfb"
}
,{
"testCaseDescription": "javascript-for-statement-delete-test",
@@ -4049,9 +4095,17 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "0267f05f5b16c04fc84af196f688f8f2d1962654",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index 39af699..de8ae87 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1,2 +1 @@",
+ "-for (i = 0, init(); i < 10; i++) { log(i); }",
+ " for (i = 0, init(); i < 100; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "902ec8d54dc2dda2609c14440b08ae81d44c4de5"
+ "shas": "030f6e47ed5f03b21e98c128d8bb398225366bfb..79269d7c37a4237b15a1cb4aa014c4f54e72faaf"
}
,{
"testCaseDescription": "javascript-for-statement-delete-rest-test",
@@ -4241,7 +4295,14 @@
"filePaths": [
"for-statement.js"
],
- "sha1": "902ec8d54dc2dda2609c14440b08ae81d44c4de5",
+ "patch": [
+ "diff --git a/for-statement.js b/for-statement.js",
+ "index de8ae87..e69de29 100644",
+ "--- a/for-statement.js",
+ "+++ b/for-statement.js",
+ "@@ -1 +0,0 @@",
+ "-for (i = 0, init(); i < 100; i++) { log(i); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5ab51e5a23cbcc433c36acf01b0f85eb614f11ab"
+ "shas": "79269d7c37a4237b15a1cb4aa014c4f54e72faaf..aa5f6a7c2031a5c8823a005dffbe948bd997e140"
}]
diff --git a/test/corpus/json/javascript/function-call-args.json b/test/corpus/json/javascript/function-call-args.json
index 95b3e4a30..54a786a8e 100644
--- a/test/corpus/json/javascript/function-call-args.json
+++ b/test/corpus/json/javascript/function-call-args.json
@@ -191,9 +191,16 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "937d4af49d1685550ae5a457368e488ed62e26b0",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index e69de29..699333d 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -0,0 +1 @@",
+ "+someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d192b9f401391fb3cc58201922a3f3a38f86b376"
+ "shas": "fc795a83fff7fcdcadac0ce15ce74b4c24bfcbd5..f0d27ee6b9aad8945ee36251c43edd314201c669"
}
,{
"testCaseDescription": "javascript-function-call-args-replacement-insert-test",
@@ -866,9 +873,18 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "d192b9f401391fb3cc58201922a3f3a38f86b376",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index 699333d..3f4ee6e 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1 +1,3 @@",
+ "+someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)",
+ "+someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "828c99d37056be7d5074627d4f9a89cdfcc4ea2c"
+ "shas": "f0d27ee6b9aad8945ee36251c43edd314201c669..d523d6414978750538a5f0db9a039430426a16bd"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-insert-test",
@@ -1855,9 +1871,19 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "828c99d37056be7d5074627d4f9a89cdfcc4ea2c",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index 3f4ee6e..dc419cb 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1,3 +1,3 @@",
+ "-someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)",
+ "+someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e9c54963235b1cce728a2b1da795345e70279297"
+ "shas": "d523d6414978750538a5f0db9a039430426a16bd..e6ce816b8aef49808b88c148091b0cc5d1b50af7"
}
,{
"testCaseDescription": "javascript-function-call-args-replacement-test",
@@ -2844,9 +2870,19 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "e9c54963235b1cce728a2b1da795345e70279297",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index dc419cb..3f4ee6e 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1,3 +1,3 @@",
+ "-someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ "+someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "36478f9d1002d8568be32ce092fd3574be8abec5"
+ "shas": "e6ce816b8aef49808b88c148091b0cc5d1b50af7..505d2d8e44416f84023a062e474ea5547a9e24ef"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-replacement-test",
@@ -3674,9 +3710,19 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "36478f9d1002d8568be32ce092fd3574be8abec5",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index 3f4ee6e..cae967b 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1,3 +1,2 @@",
+ "-someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)",
+ "-someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ "+someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0deab1f16c63033b1d3b4462e470d98020edcba4"
+ "shas": "505d2d8e44416f84023a062e474ea5547a9e24ef..3993b0e88ee0edfd98dda259fc787ba4845495d4"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-test",
@@ -4194,9 +4240,17 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "0deab1f16c63033b1d3b4462e470d98020edcba4",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index cae967b..0d19573 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1,2 +1 @@",
+ "-someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)",
+ " someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "00cc8a62463306165fa4e392873d1481e7902faf"
+ "shas": "3993b0e88ee0edfd98dda259fc787ba4845495d4..f89ece40228968ba4db1a434efef2d7dcb2299f1"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-rest-test",
@@ -4391,7 +4445,14 @@
"filePaths": [
"function-call-args.js"
],
- "sha1": "00cc8a62463306165fa4e392873d1481e7902faf",
+ "patch": [
+ "diff --git a/function-call-args.js b/function-call-args.js",
+ "index 0d19573..e69de29 100644",
+ "--- a/function-call-args.js",
+ "+++ b/function-call-args.js",
+ "@@ -1 +0,0 @@",
+ "-someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d25c261f3d2c8744d5569a69d8df9e762b5218a4"
+ "shas": "f89ece40228968ba4db1a434efef2d7dcb2299f1..24ed5bdc27489ca788d6784b0385a26f77c8c9d7"
}]
diff --git a/test/corpus/json/javascript/function-call.json b/test/corpus/json/javascript/function-call.json
index e943fc20f..761c5386f 100644
--- a/test/corpus/json/javascript/function-call.json
+++ b/test/corpus/json/javascript/function-call.json
@@ -97,9 +97,16 @@
"filePaths": [
"function-call.js"
],
- "sha1": "28e5cd02261633e062e3045a97dd37064d506a0c",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index e69de29..8bd95e0 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -0,0 +1 @@",
+ "+someFunction(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a5ebc2b5bf2f7d5b910a31060f5949014c3dd779"
+ "shas": "2f1a5ed4016f7e817cb5b1b4839bb64deecd8042..25d3ee2d3ff91913572423be561a8318988efc61"
}
,{
"testCaseDescription": "javascript-function-call-replacement-insert-test",
@@ -396,9 +403,18 @@
"filePaths": [
"function-call.js"
],
- "sha1": "a5ebc2b5bf2f7d5b910a31060f5949014c3dd779",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index 8bd95e0..6bb4cf3 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1 +1,3 @@",
+ "+someFunction(arg1, \"arg3\");",
+ "+someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "57f9b1954a91b9fb73f141cb4bad001e65e5c3f2"
+ "shas": "25d3ee2d3ff91913572423be561a8318988efc61..eaf1c7143170b44b39118ef3cdcd21d5ffea14b3"
}
,{
"testCaseDescription": "javascript-function-call-delete-insert-test",
@@ -811,9 +827,19 @@
"filePaths": [
"function-call.js"
],
- "sha1": "57f9b1954a91b9fb73f141cb4bad001e65e5c3f2",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index 6bb4cf3..b38c232 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-someFunction(arg1, \"arg3\");",
+ "+someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "41e8b2df0a9bd1c2f784cb61e50657c5dacd1237"
+ "shas": "eaf1c7143170b44b39118ef3cdcd21d5ffea14b3..a338d8f70dc78ffafe94e2ba9c900cb2df7e8609"
}
,{
"testCaseDescription": "javascript-function-call-replacement-test",
@@ -1226,9 +1252,19 @@
"filePaths": [
"function-call.js"
],
- "sha1": "41e8b2df0a9bd1c2f784cb61e50657c5dacd1237",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index b38c232..6bb4cf3 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-someFunction(arg1, \"arg2\");",
+ "+someFunction(arg1, \"arg3\");",
+ " someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0395a3842550da96dc602d1a2042c5847c91811d"
+ "shas": "a338d8f70dc78ffafe94e2ba9c900cb2df7e8609..6084db51a20a9a4460c86208fda30bfcd92cb316"
}
,{
"testCaseDescription": "javascript-function-call-delete-replacement-test",
@@ -1586,9 +1622,19 @@
"filePaths": [
"function-call.js"
],
- "sha1": "0395a3842550da96dc602d1a2042c5847c91811d",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index 6bb4cf3..3e15c6a 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1,3 +1,2 @@",
+ "-someFunction(arg1, \"arg3\");",
+ "-someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg2\");",
+ "+someFunction(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "581f83c56791b57aa4ffc4f0448e0326629af671"
+ "shas": "6084db51a20a9a4460c86208fda30bfcd92cb316..895672cc7bd62b5e5824ea70785c8f0eccb41d79"
}
,{
"testCaseDescription": "javascript-function-call-delete-test",
@@ -1824,9 +1870,17 @@
"filePaths": [
"function-call.js"
],
- "sha1": "581f83c56791b57aa4ffc4f0448e0326629af671",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index 3e15c6a..1add64b 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1,2 +1 @@",
+ "-someFunction(arg1, \"arg2\");",
+ " someFunction(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "750c9f9102bb5efd7418ade5195f10583b6479b6"
+ "shas": "895672cc7bd62b5e5824ea70785c8f0eccb41d79..5698ffbd0ba7c682461b54b92c9036844cf7598e"
}
,{
"testCaseDescription": "javascript-function-call-delete-rest-test",
@@ -1927,7 +1981,14 @@
"filePaths": [
"function-call.js"
],
- "sha1": "750c9f9102bb5efd7418ade5195f10583b6479b6",
+ "patch": [
+ "diff --git a/function-call.js b/function-call.js",
+ "index 1add64b..e69de29 100644",
+ "--- a/function-call.js",
+ "+++ b/function-call.js",
+ "@@ -1 +0,0 @@",
+ "-someFunction(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1011f24f71bd4ec75766ffbe5d5a27d625dabc58"
+ "shas": "5698ffbd0ba7c682461b54b92c9036844cf7598e..7aca49a04758f43f9e7c909ee616f33c18cf0e27"
}]
diff --git a/test/corpus/json/javascript/function.json b/test/corpus/json/javascript/function.json
index d796f7a50..037339f45 100644
--- a/test/corpus/json/javascript/function.json
+++ b/test/corpus/json/javascript/function.json
@@ -115,9 +115,16 @@
"filePaths": [
"function.js"
],
- "sha1": "aab3cdb03018b80452f88033908dda159df29b58",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index e69de29..2d8d739 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -0,0 +1 @@",
+ "+function(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "feb51095da5217fff9f3f88509c44092f9474faf"
+ "shas": "47efa692005800aae87fccdba3a089c87d9c46f1..f24028d8eb97ae574ac7e8a0ad7a20c08ce93139"
}
,{
"testCaseDescription": "javascript-function-replacement-insert-test",
@@ -486,9 +493,18 @@
"filePaths": [
"function.js"
],
- "sha1": "feb51095da5217fff9f3f88509c44092f9474faf",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index 2d8d739..4389406 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1 +1,3 @@",
+ "+function(arg1, arg2) { arg1; };",
+ "+function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "10724662384505ec28647a77d9e8b3bda19d4996"
+ "shas": "f24028d8eb97ae574ac7e8a0ad7a20c08ce93139..88f2dd5809a7bafd96d27ebf18b4daafef783a3b"
}
,{
"testCaseDescription": "javascript-function-delete-insert-test",
@@ -1009,9 +1025,19 @@
"filePaths": [
"function.js"
],
- "sha1": "10724662384505ec28647a77d9e8b3bda19d4996",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index 4389406..924c99e 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function(arg1, arg2) { arg1; };",
+ "+function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9c499a71d11fd4d8bd70c624d21d08b93bbda046"
+ "shas": "88f2dd5809a7bafd96d27ebf18b4daafef783a3b..74c5830b3ef3429cb69c367c5cc475c65b12ce53"
}
,{
"testCaseDescription": "javascript-function-replacement-test",
@@ -1532,9 +1558,19 @@
"filePaths": [
"function.js"
],
- "sha1": "9c499a71d11fd4d8bd70c624d21d08b93bbda046",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index 924c99e..4389406 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function(arg1, arg2) { arg2; };",
+ "+function(arg1, arg2) { arg1; };",
+ " function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "53fa94aa2cbea7a0bf988a5464b1cfd42dddb511"
+ "shas": "74c5830b3ef3429cb69c367c5cc475c65b12ce53..9b9ec597e957a243d5675aa0b091204ddf2ad7c9"
}
,{
"testCaseDescription": "javascript-function-delete-replacement-test",
@@ -1982,9 +2018,19 @@
"filePaths": [
"function.js"
],
- "sha1": "53fa94aa2cbea7a0bf988a5464b1cfd42dddb511",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index 4389406..254dbcf 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function(arg1, arg2) { arg1; };",
+ "-function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg2; };",
+ "+function(arg1, arg2) { arg1; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "23714bebfe8d251f229bf6437de747b3a603c756"
+ "shas": "9b9ec597e957a243d5675aa0b091204ddf2ad7c9..47e9bce142789a8a4d674e20982dce0d8a0c90b5"
}
,{
"testCaseDescription": "javascript-function-delete-test",
@@ -2274,9 +2320,17 @@
"filePaths": [
"function.js"
],
- "sha1": "23714bebfe8d251f229bf6437de747b3a603c756",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index 254dbcf..b37e867 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1,2 +1 @@",
+ "-function(arg1, arg2) { arg2; };",
+ " function(arg1, arg2) { arg1; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "497146f008b62415f35f20f169c8beba03980b72"
+ "shas": "47e9bce142789a8a4d674e20982dce0d8a0c90b5..5781ccafc974bef5785ff1533042f7eccba7ff03"
}
,{
"testCaseDescription": "javascript-function-delete-rest-test",
@@ -2395,7 +2449,14 @@
"filePaths": [
"function.js"
],
- "sha1": "497146f008b62415f35f20f169c8beba03980b72",
+ "patch": [
+ "diff --git a/function.js b/function.js",
+ "index b37e867..e69de29 100644",
+ "--- a/function.js",
+ "+++ b/function.js",
+ "@@ -1 +0,0 @@",
+ "-function(arg1, arg2) { arg1; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a83003e88deb30e0a3c4f7d369c0aa0a24986a82"
+ "shas": "5781ccafc974bef5785ff1533042f7eccba7ff03..4a56270744e8c9a123c828e7ab9409789ab51e5b"
}]
diff --git a/test/corpus/json/javascript/generator-function.json b/test/corpus/json/javascript/generator-function.json
index 81552dd7e..3d12c8516 100644
--- a/test/corpus/json/javascript/generator-function.json
+++ b/test/corpus/json/javascript/generator-function.json
@@ -129,9 +129,16 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "cbcb5d062890692a2a789b510fe5ca42f93fbae0",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index e69de29..04e8a59 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -0,0 +1 @@",
+ "+function *generateStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d8ab3aa4042a2054274acfd0d9cadfb34508da97"
+ "shas": "a52e2d614f9e9504970732cbc2d5f9c933eb061f..a4a896cba2216edee62cc9fe96efdbc5408fdb46"
}
,{
"testCaseDescription": "javascript-generator-function-replacement-insert-test",
@@ -556,9 +563,18 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "d8ab3aa4042a2054274acfd0d9cadfb34508da97",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index 04e8a59..ed5c037 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1 +1,3 @@",
+ "+function *generateNewStuff(arg1, arg2) { yield; yield arg2; };",
+ "+function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d6e10d7d2dc19527725f2520be455028c06d6c1b"
+ "shas": "a4a896cba2216edee62cc9fe96efdbc5408fdb46..efb9d38a6460f6bac29b03924c33ee9bce0b26d2"
}
,{
"testCaseDescription": "javascript-generator-function-delete-insert-test",
@@ -1163,9 +1179,19 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "d6e10d7d2dc19527725f2520be455028c06d6c1b",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index ed5c037..0895c3f 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function *generateNewStuff(arg1, arg2) { yield; yield arg2; };",
+ "+function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4c537f6b60b1ef1d082f62e211b6f4da62918d0f"
+ "shas": "efb9d38a6460f6bac29b03924c33ee9bce0b26d2..129fc139ed29b7d14c49713f6297e118f3691d9c"
}
,{
"testCaseDescription": "javascript-generator-function-replacement-test",
@@ -1770,9 +1796,19 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "4c537f6b60b1ef1d082f62e211b6f4da62918d0f",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index 0895c3f..ed5c037 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ "+function *generateNewStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "61b80bc773db77b10bf1da88f0fde3c935d0f5aa"
+ "shas": "129fc139ed29b7d14c49713f6297e118f3691d9c..0360112c551e3312985cfefd8c393f5ee1ea75ba"
}
,{
"testCaseDescription": "javascript-generator-function-delete-replacement-test",
@@ -2290,9 +2326,19 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "61b80bc773db77b10bf1da88f0fde3c935d0f5aa",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index ed5c037..1dae105 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function *generateNewStuff(arg1, arg2) { yield; yield arg2; };",
+ "-function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ "+function *generateNewStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7416033e4d4abc9a83e7ce333623fb3fb8a2926b"
+ "shas": "0360112c551e3312985cfefd8c393f5ee1ea75ba..cd60754110e1117c82342762bc3e2f924a91d2f7"
}
,{
"testCaseDescription": "javascript-generator-function-delete-test",
@@ -2624,9 +2670,17 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "7416033e4d4abc9a83e7ce333623fb3fb8a2926b",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index 1dae105..5846d1c 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1,2 +1 @@",
+ "-function *generateStuff(arg1, arg2) { yield; yield arg2; };",
+ " function *generateNewStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a37529aaa73a8cefb09a4b4ac418c18e0c6cd5c3"
+ "shas": "cd60754110e1117c82342762bc3e2f924a91d2f7..99fb44113edd307ee060aa841b283093ac2d6f34"
}
,{
"testCaseDescription": "javascript-generator-function-delete-rest-test",
@@ -2759,7 +2813,14 @@
"filePaths": [
"generator-function.js"
],
- "sha1": "a37529aaa73a8cefb09a4b4ac418c18e0c6cd5c3",
+ "patch": [
+ "diff --git a/generator-function.js b/generator-function.js",
+ "index 5846d1c..e69de29 100644",
+ "--- a/generator-function.js",
+ "+++ b/generator-function.js",
+ "@@ -1 +0,0 @@",
+ "-function *generateNewStuff(arg1, arg2) { yield; yield arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2e98846e3a927bbf738f7d46ca9b6746840b89a7"
+ "shas": "99fb44113edd307ee060aa841b283093ac2d6f34..e3b9f963811fa510e777ed818a75408691e53555"
}]
diff --git a/test/corpus/json/javascript/identifier.json b/test/corpus/json/javascript/identifier.json
index 7021fd7ed..14a895c72 100644
--- a/test/corpus/json/javascript/identifier.json
+++ b/test/corpus/json/javascript/identifier.json
@@ -74,9 +74,16 @@
"filePaths": [
"identifier.js"
],
- "sha1": "81080589255cbb551f9a84c4691635b5fd543c2e",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index e69de29..1cf4ad0 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -0,0 +1 @@",
+ "+theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ecef53a7ab2ea21c22edfaa21eb069c0c9d41235"
+ "shas": "1b8151602239d34159506d5d6e55de712e8c0d10..b4bc6d6ee5fd674fc9dbc5880f2734283a79c445"
}
,{
"testCaseDescription": "javascript-identifier-replacement-insert-test",
@@ -281,9 +288,18 @@
"filePaths": [
"identifier.js"
],
- "sha1": "ecef53a7ab2ea21c22edfaa21eb069c0c9d41235",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index 1cf4ad0..888855a 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1 +1,3 @@",
+ "+theVar2",
+ "+theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fdd737dd848377b09c5c9ad82a6722875f06bb47"
+ "shas": "b4bc6d6ee5fd674fc9dbc5880f2734283a79c445..65c8ab30e080fc1e8a7a78a09d9a65ff4d70243d"
}
,{
"testCaseDescription": "javascript-identifier-delete-insert-test",
@@ -558,9 +574,19 @@
"filePaths": [
"identifier.js"
],
- "sha1": "fdd737dd848377b09c5c9ad82a6722875f06bb47",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index 888855a..60e041c 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1,3 +1,3 @@",
+ "-theVar2",
+ "+theVar;",
+ " theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f2326c74a26754776cb9c4595cdad8ce819dea10"
+ "shas": "65c8ab30e080fc1e8a7a78a09d9a65ff4d70243d..df5af19f39fbf09f64f8cf679e07b2b1020fbe28"
}
,{
"testCaseDescription": "javascript-identifier-replacement-test",
@@ -835,9 +861,19 @@
"filePaths": [
"identifier.js"
],
- "sha1": "f2326c74a26754776cb9c4595cdad8ce819dea10",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index 60e041c..888855a 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1,3 +1,3 @@",
+ "-theVar;",
+ "+theVar2",
+ " theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "696d457e64d47b3cf9d6f232259f3c576de83d28"
+ "shas": "df5af19f39fbf09f64f8cf679e07b2b1020fbe28..935bdc032c3cacf8565bd269fa6c7f525c9a83b7"
}
,{
"testCaseDescription": "javascript-identifier-delete-replacement-test",
@@ -1080,9 +1116,19 @@
"filePaths": [
"identifier.js"
],
- "sha1": "696d457e64d47b3cf9d6f232259f3c576de83d28",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index 888855a..fbc7b28 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1,3 +1,2 @@",
+ "-theVar2",
+ "-theVar;",
+ " theVar;",
+ "+theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "333d96cdd04df8078ee0520f047d1c966040fe6d"
+ "shas": "935bdc032c3cacf8565bd269fa6c7f525c9a83b7..99a3a4e1f2f45b9d0bd677e3252572fbdd77b297"
}
,{
"testCaseDescription": "javascript-identifier-delete-test",
@@ -1249,9 +1295,17 @@
"filePaths": [
"identifier.js"
],
- "sha1": "333d96cdd04df8078ee0520f047d1c966040fe6d",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index fbc7b28..7276d95 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1,2 +1 @@",
+ "-theVar;",
+ " theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "99939c64d721c781a23f3f138d190c11b04b7f90"
+ "shas": "99a3a4e1f2f45b9d0bd677e3252572fbdd77b297..433e03b741975ca0b158e12ddd46c4ade00bf61d"
}
,{
"testCaseDescription": "javascript-identifier-delete-rest-test",
@@ -1329,7 +1383,14 @@
"filePaths": [
"identifier.js"
],
- "sha1": "99939c64d721c781a23f3f138d190c11b04b7f90",
+ "patch": [
+ "diff --git a/identifier.js b/identifier.js",
+ "index 7276d95..e69de29 100644",
+ "--- a/identifier.js",
+ "+++ b/identifier.js",
+ "@@ -1 +0,0 @@",
+ "-theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f8073abc47cb34b48625b1088eecc41cf0e51748"
+ "shas": "433e03b741975ca0b158e12ddd46c4ade00bf61d..de56bb89881ee1f97c710b8447f22a479a373692"
}]
diff --git a/test/corpus/json/javascript/if-else.json b/test/corpus/json/javascript/if-else.json
index 96f6824d3..16cff46f4 100644
--- a/test/corpus/json/javascript/if-else.json
+++ b/test/corpus/json/javascript/if-else.json
@@ -59,92 +59,92 @@
22,
24
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 34,
+ 35
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 37,
+ 38
+ ]
+ }
+ ],
+ "range": [
+ 37,
+ 39
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 49,
+ 50
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 52,
+ 53
+ ]
+ }
+ ],
+ "range": [
+ 52,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 60,
+ 61
+ ]
+ }
+ ],
+ "range": [
+ 60,
+ 62
+ ]
+ }
+ ],
+ "range": [
+ 45,
+ 62
+ ]
+ }
+ ],
+ "range": [
+ 30,
+ 62
+ ]
}
],
"range": [
15,
62
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 34,
- 35
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 37,
- 38
- ]
- }
- ],
- "range": [
- 37,
- 39
- ]
- }
- ],
- "range": [
- 30,
- 62
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 49,
- 50
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 52,
- 53
- ]
- }
- ],
- "range": [
- 52,
- 54
- ]
- }
- ],
- "range": [
- 45,
- 62
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 60,
- 61
- ]
- }
- ],
- "range": [
- 60,
- 62
- ]
}
],
"range": [
@@ -202,9 +202,16 @@
"filePaths": [
"if-else.js"
],
- "sha1": "0d04a39119475382fd1b236c00355a271286be24",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index e69de29..d81ebad 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -0,0 +1 @@",
+ "+if (x) y; else if (a) b; else if (c) d; else if (e) f; else g"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "42654e7cd95ecace76558f048acf9d87ac92875c"
+ "shas": "a7c68af9b8e2a95ea64781f7701d616d9831d54b..859101c77238fb0c59826bfa95b840d6ce142fe4"
}
,{
"testCaseDescription": "javascript-if-else-replacement-insert-test",
@@ -276,99 +283,99 @@
22,
28
]
- }
- ],
- "range": [
- 15,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 38,
- 39
- ]
},
{
- "category": "ExpressionStatements",
+ "category": "If",
"children": [
{
"category": "Identifier",
"range": [
- 41,
- 42
+ 38,
+ 39
]
- }
- ],
- "range": [
- 41,
- 43
- ]
- }
- ],
- "range": [
- 34,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 53,
- 54
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
+ },
{
"category": "ExpressionStatements",
"children": [
{
"category": "Identifier",
"range": [
- 58,
- 59
+ 41,
+ 42
]
}
],
"range": [
- 58,
- 60
+ 41,
+ 43
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 53,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 58,
+ 59
+ ]
+ }
+ ],
+ "range": [
+ 58,
+ 60
+ ]
+ }
+ ],
+ "range": [
+ 56,
+ 62
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 68,
+ 69
+ ]
+ }
+ ],
+ "range": [
+ 68,
+ 70
+ ]
+ }
+ ],
+ "range": [
+ 49,
+ 70
]
}
],
"range": [
- 56,
- 62
+ 34,
+ 70
]
}
],
"range": [
- 49,
- 70
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 68,
- 69
- ]
- }
- ],
- "range": [
- 68,
+ 15,
70
]
}
@@ -451,92 +458,92 @@
92,
94
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 104,
+ 105
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 107,
+ 108
+ ]
+ }
+ ],
+ "range": [
+ 107,
+ 109
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 119,
+ 120
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 122,
+ 123
+ ]
+ }
+ ],
+ "range": [
+ 122,
+ 124
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 130,
+ 131
+ ]
+ }
+ ],
+ "range": [
+ 130,
+ 132
+ ]
+ }
+ ],
+ "range": [
+ 115,
+ 132
+ ]
+ }
+ ],
+ "range": [
+ 100,
+ 132
+ ]
}
],
"range": [
85,
132
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 104,
- 105
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 107,
- 108
- ]
- }
- ],
- "range": [
- 107,
- 109
- ]
- }
- ],
- "range": [
- 100,
- 132
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 119,
- 120
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 122,
- 123
- ]
- }
- ],
- "range": [
- 122,
- 124
- ]
- }
- ],
- "range": [
- 115,
- 132
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 130,
- 131
- ]
- }
- ],
- "range": [
- 130,
- 132
- ]
}
],
"patch": "insert",
@@ -617,92 +624,92 @@
22,
24
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 34,
+ 35
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 37,
+ 38
+ ]
+ }
+ ],
+ "range": [
+ 37,
+ 39
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 49,
+ 50
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 52,
+ 53
+ ]
+ }
+ ],
+ "range": [
+ 52,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 60,
+ 61
+ ]
+ }
+ ],
+ "range": [
+ 60,
+ 62
+ ]
+ }
+ ],
+ "range": [
+ 45,
+ 62
+ ]
+ }
+ ],
+ "range": [
+ 30,
+ 62
+ ]
}
],
"range": [
15,
62
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 34,
- 35
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 37,
- 38
- ]
- }
- ],
- "range": [
- 37,
- 39
- ]
- }
- ],
- "range": [
- 30,
- 62
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 49,
- 50
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 52,
- 53
- ]
- }
- ],
- "range": [
- 52,
- 54
- ]
- }
- ],
- "range": [
- 45,
- 62
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 60,
- 61
- ]
- }
- ],
- "range": [
- 60,
- 62
- ]
}
],
"range": [
@@ -780,92 +787,92 @@
154,
156
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 166,
+ 167
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 169,
+ 170
+ ]
+ }
+ ],
+ "range": [
+ 169,
+ 171
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 181,
+ 182
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 184,
+ 185
+ ]
+ }
+ ],
+ "range": [
+ 184,
+ 186
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 192,
+ 193
+ ]
+ }
+ ],
+ "range": [
+ 192,
+ 194
+ ]
+ }
+ ],
+ "range": [
+ 177,
+ 194
+ ]
+ }
+ ],
+ "range": [
+ 162,
+ 194
+ ]
}
],
"range": [
147,
194
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 166,
- 167
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 169,
- 170
- ]
- }
- ],
- "range": [
- 169,
- 171
- ]
- }
- ],
- "range": [
- 162,
- 194
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 181,
- 182
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 184,
- 185
- ]
- }
- ],
- "range": [
- 184,
- 186
- ]
- }
- ],
- "range": [
- 177,
- 194
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 192,
- 193
- ]
- }
- ],
- "range": [
- 192,
- 194
- ]
}
],
"range": [
@@ -939,9 +946,18 @@
"filePaths": [
"if-else.js"
],
- "sha1": "42654e7cd95ecace76558f048acf9d87ac92875c",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index d81ebad..6bb0eaa 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1 +1,3 @@",
+ "+if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o",
+ "+if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7d03c150c3442ed373191c9cff1785b60caa8c21"
+ "shas": "859101c77238fb0c59826bfa95b840d6ce142fe4..7aa5ca0081c95e390cc3fb383e893ad607d21ac6"
}
,{
"testCaseDescription": "javascript-if-else-delete-insert-test",
@@ -1017,104 +1033,104 @@
22,
28
]
- }
- ],
- "range": [
- 15,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 38,
- 39
- ]
},
{
- "category": "ExpressionStatements",
+ "category": "If",
"children": [
{
"category": "Identifier",
"patch": "replace",
"range": [
- 41,
- 42
+ 38,
+ 39
]
- }
- ],
- "range": [
- 41,
- 43
- ]
- }
- ],
- "range": [
- 34,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 53,
- 54
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
+ },
{
"category": "ExpressionStatements",
"children": [
{
"category": "Identifier",
+ "patch": "replace",
"range": [
- 58,
- 59
+ 41,
+ 42
]
}
],
- "patch": "delete",
"range": [
- 58,
- 60
+ 41,
+ 43
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "replace",
+ "range": [
+ 53,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 58,
+ 59
+ ]
+ }
+ ],
+ "patch": "delete",
+ "range": [
+ 58,
+ 60
+ ]
+ }
+ ],
+ "range": [
+ 56,
+ 62
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "replace",
+ "range": [
+ 68,
+ 69
+ ]
+ }
+ ],
+ "range": [
+ 68,
+ 70
+ ]
+ }
+ ],
+ "range": [
+ 49,
+ 70
]
}
],
"range": [
- 56,
- 62
+ 34,
+ 70
]
}
],
"range": [
- 49,
- 70
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 68,
- 69
- ]
- }
- ],
- "range": [
- 68,
+ 15,
70
]
}
@@ -1198,95 +1214,95 @@
22,
24
]
- }
- ],
- "range": [
- 15,
- 62
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 34,
- 35
- ]
},
{
- "category": "ExpressionStatements",
+ "category": "If",
"children": [
{
"category": "Identifier",
"patch": "replace",
"range": [
- 37,
- 38
+ 34,
+ 35
]
- }
- ],
- "range": [
- 37,
- 39
- ]
- }
- ],
- "range": [
- 30,
- 62
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 49,
- 50
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
+ },
{
- "category": "Identifier",
- "patch": "insert",
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "replace",
+ "range": [
+ 37,
+ 38
+ ]
+ }
+ ],
"range": [
- 52,
- 53
+ 37,
+ 39
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "replace",
+ "range": [
+ 49,
+ 50
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "insert",
+ "range": [
+ 52,
+ 53
+ ]
+ }
+ ],
+ "range": [
+ 52,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "replace",
+ "range": [
+ 60,
+ 61
+ ]
+ }
+ ],
+ "range": [
+ 60,
+ 62
+ ]
+ }
+ ],
+ "range": [
+ 45,
+ 62
]
}
],
"range": [
- 52,
- 54
+ 30,
+ 62
]
}
],
"range": [
- 45,
- 62
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 60,
- 61
- ]
- }
- ],
- "range": [
- 60,
+ 15,
62
]
}
@@ -1368,92 +1384,92 @@
92,
94
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 104,
+ 105
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 107,
+ 108
+ ]
+ }
+ ],
+ "range": [
+ 107,
+ 109
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 119,
+ 120
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 122,
+ 123
+ ]
+ }
+ ],
+ "range": [
+ 122,
+ 124
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 130,
+ 131
+ ]
+ }
+ ],
+ "range": [
+ 130,
+ 132
+ ]
+ }
+ ],
+ "range": [
+ 115,
+ 132
+ ]
+ }
+ ],
+ "range": [
+ 100,
+ 132
+ ]
}
],
"range": [
85,
132
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 104,
- 105
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 107,
- 108
- ]
- }
- ],
- "range": [
- 107,
- 109
- ]
- }
- ],
- "range": [
- 100,
- 132
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 119,
- 120
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 122,
- 123
- ]
- }
- ],
- "range": [
- 122,
- 124
- ]
- }
- ],
- "range": [
- 115,
- 132
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 130,
- 131
- ]
- }
- ],
- "range": [
- 130,
- 132
- ]
}
],
"range": [
@@ -1531,92 +1547,92 @@
84,
86
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 96,
+ 97
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 99,
+ 100
+ ]
+ }
+ ],
+ "range": [
+ 99,
+ 101
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 111,
+ 112
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 114,
+ 115
+ ]
+ }
+ ],
+ "range": [
+ 114,
+ 116
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 122,
+ 123
+ ]
+ }
+ ],
+ "range": [
+ 122,
+ 124
+ ]
+ }
+ ],
+ "range": [
+ 107,
+ 124
+ ]
+ }
+ ],
+ "range": [
+ 92,
+ 124
+ ]
}
],
"range": [
77,
124
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 96,
- 97
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 99,
- 100
- ]
- }
- ],
- "range": [
- 99,
- 101
- ]
- }
- ],
- "range": [
- 92,
- 124
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 111,
- 112
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 114,
- 115
- ]
- }
- ],
- "range": [
- 114,
- 116
- ]
- }
- ],
- "range": [
- 107,
- 124
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 122,
- 123
- ]
- }
- ],
- "range": [
- 122,
- 124
- ]
}
],
"range": [
@@ -1696,92 +1712,92 @@
154,
156
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 166,
+ 167
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 169,
+ 170
+ ]
+ }
+ ],
+ "range": [
+ 169,
+ 171
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 181,
+ 182
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 184,
+ 185
+ ]
+ }
+ ],
+ "range": [
+ 184,
+ 186
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 192,
+ 193
+ ]
+ }
+ ],
+ "range": [
+ 192,
+ 194
+ ]
+ }
+ ],
+ "range": [
+ 177,
+ 194
+ ]
+ }
+ ],
+ "range": [
+ 162,
+ 194
+ ]
}
],
"range": [
147,
194
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 166,
- 167
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 169,
- 170
- ]
- }
- ],
- "range": [
- 169,
- 171
- ]
- }
- ],
- "range": [
- 162,
- 194
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 181,
- 182
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 184,
- 185
- ]
- }
- ],
- "range": [
- 184,
- 186
- ]
- }
- ],
- "range": [
- 177,
- 194
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 192,
- 193
- ]
- }
- ],
- "range": [
- 192,
- 194
- ]
}
],
"range": [
@@ -1859,92 +1875,92 @@
146,
148
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 158,
+ 159
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 161,
+ 162
+ ]
+ }
+ ],
+ "range": [
+ 161,
+ 163
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 173,
+ 174
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 176,
+ 177
+ ]
+ }
+ ],
+ "range": [
+ 176,
+ 178
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 184,
+ 185
+ ]
+ }
+ ],
+ "range": [
+ 184,
+ 186
+ ]
+ }
+ ],
+ "range": [
+ 169,
+ 186
+ ]
+ }
+ ],
+ "range": [
+ 154,
+ 186
+ ]
}
],
"range": [
139,
186
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 158,
- 159
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 161,
- 162
- ]
- }
- ],
- "range": [
- 161,
- 163
- ]
- }
- ],
- "range": [
- 154,
- 186
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 173,
- 174
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 176,
- 177
- ]
- }
- ],
- "range": [
- 176,
- 178
- ]
- }
- ],
- "range": [
- 169,
- 186
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 184,
- 185
- ]
- }
- ],
- "range": [
- 184,
- 186
- ]
}
],
"range": [
@@ -2018,9 +2034,19 @@
"filePaths": [
"if-else.js"
],
- "sha1": "7d03c150c3442ed373191c9cff1785b60caa8c21",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index 6bb0eaa..2034be1 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1,3 +1,3 @@",
+ "-if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o",
+ "+if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a1cc4fcd595d3dc8c9ef506cfef89ef93af156a2"
+ "shas": "7aa5ca0081c95e390cc3fb383e893ad607d21ac6..db2dc88faaeca02e77d4d12d5c72988d460da4aa"
}
,{
"testCaseDescription": "javascript-if-else-replacement-test",
@@ -2087,95 +2113,95 @@
22,
24
]
- }
- ],
- "range": [
- 15,
- 62
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 34,
- 35
- ]
},
{
- "category": "ExpressionStatements",
+ "category": "If",
"children": [
{
"category": "Identifier",
"patch": "replace",
"range": [
- 37,
- 38
+ 34,
+ 35
]
- }
- ],
- "range": [
- 37,
- 39
- ]
- }
- ],
- "range": [
- 30,
- 62
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 49,
- 50
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
+ },
{
- "category": "Identifier",
- "patch": "delete",
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "replace",
+ "range": [
+ 37,
+ 38
+ ]
+ }
+ ],
"range": [
- 52,
- 53
+ 37,
+ 39
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "replace",
+ "range": [
+ 49,
+ 50
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "delete",
+ "range": [
+ 52,
+ 53
+ ]
+ }
+ ],
+ "range": [
+ 52,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "replace",
+ "range": [
+ 60,
+ 61
+ ]
+ }
+ ],
+ "range": [
+ 60,
+ 62
+ ]
+ }
+ ],
+ "range": [
+ 45,
+ 62
]
}
],
"range": [
- 52,
- 54
+ 30,
+ 62
]
}
],
"range": [
- 45,
- 62
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 60,
- 61
- ]
- }
- ],
- "range": [
- 60,
+ 15,
62
]
}
@@ -2268,104 +2294,104 @@
22,
28
]
- }
- ],
- "range": [
- 15,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 38,
- 39
- ]
},
{
- "category": "ExpressionStatements",
+ "category": "If",
"children": [
{
"category": "Identifier",
"patch": "replace",
"range": [
- 41,
- 42
+ 38,
+ 39
]
- }
- ],
- "range": [
- 41,
- 43
- ]
- }
- ],
- "range": [
- 34,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 53,
- 54
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
+ },
{
"category": "ExpressionStatements",
"children": [
{
"category": "Identifier",
+ "patch": "replace",
"range": [
- 58,
- 59
+ 41,
+ 42
]
}
],
- "patch": "insert",
"range": [
- 58,
- 60
+ 41,
+ 43
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "replace",
+ "range": [
+ 53,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 58,
+ 59
+ ]
+ }
+ ],
+ "patch": "insert",
+ "range": [
+ 58,
+ 60
+ ]
+ }
+ ],
+ "range": [
+ 56,
+ 62
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "patch": "replace",
+ "range": [
+ 68,
+ 69
+ ]
+ }
+ ],
+ "range": [
+ 68,
+ 70
+ ]
+ }
+ ],
+ "range": [
+ 49,
+ 70
]
}
],
"range": [
- 56,
- 62
+ 34,
+ 70
]
}
],
"range": [
- 49,
- 70
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "patch": "replace",
- "range": [
- 68,
- 69
- ]
- }
- ],
- "range": [
- 68,
+ 15,
70
]
}
@@ -2447,92 +2473,92 @@
84,
86
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 96,
+ 97
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 99,
+ 100
+ ]
+ }
+ ],
+ "range": [
+ 99,
+ 101
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 111,
+ 112
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 114,
+ 115
+ ]
+ }
+ ],
+ "range": [
+ 114,
+ 116
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 122,
+ 123
+ ]
+ }
+ ],
+ "range": [
+ 122,
+ 124
+ ]
+ }
+ ],
+ "range": [
+ 107,
+ 124
+ ]
+ }
+ ],
+ "range": [
+ 92,
+ 124
+ ]
}
],
"range": [
77,
124
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 96,
- 97
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 99,
- 100
- ]
- }
- ],
- "range": [
- 99,
- 101
- ]
- }
- ],
- "range": [
- 92,
- 124
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 111,
- 112
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 114,
- 115
- ]
- }
- ],
- "range": [
- 114,
- 116
- ]
- }
- ],
- "range": [
- 107,
- 124
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 122,
- 123
- ]
- }
- ],
- "range": [
- 122,
- 124
- ]
}
],
"range": [
@@ -2610,92 +2636,92 @@
92,
94
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 104,
+ 105
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 107,
+ 108
+ ]
+ }
+ ],
+ "range": [
+ 107,
+ 109
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 119,
+ 120
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 122,
+ 123
+ ]
+ }
+ ],
+ "range": [
+ 122,
+ 124
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 130,
+ 131
+ ]
+ }
+ ],
+ "range": [
+ 130,
+ 132
+ ]
+ }
+ ],
+ "range": [
+ 115,
+ 132
+ ]
+ }
+ ],
+ "range": [
+ 100,
+ 132
+ ]
}
],
"range": [
85,
132
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 104,
- 105
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 107,
- 108
- ]
- }
- ],
- "range": [
- 107,
- 109
- ]
- }
- ],
- "range": [
- 100,
- 132
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 119,
- 120
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 122,
- 123
- ]
- }
- ],
- "range": [
- 122,
- 124
- ]
- }
- ],
- "range": [
- 115,
- 132
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 130,
- 131
- ]
- }
- ],
- "range": [
- 130,
- 132
- ]
}
],
"range": [
@@ -2775,92 +2801,92 @@
146,
148
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 158,
+ 159
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 161,
+ 162
+ ]
+ }
+ ],
+ "range": [
+ 161,
+ 163
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 173,
+ 174
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 176,
+ 177
+ ]
+ }
+ ],
+ "range": [
+ 176,
+ 178
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 184,
+ 185
+ ]
+ }
+ ],
+ "range": [
+ 184,
+ 186
+ ]
+ }
+ ],
+ "range": [
+ 169,
+ 186
+ ]
+ }
+ ],
+ "range": [
+ 154,
+ 186
+ ]
}
],
"range": [
139,
186
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 158,
- 159
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 161,
- 162
- ]
- }
- ],
- "range": [
- 161,
- 163
- ]
- }
- ],
- "range": [
- 154,
- 186
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 173,
- 174
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 176,
- 177
- ]
- }
- ],
- "range": [
- 176,
- 178
- ]
- }
- ],
- "range": [
- 169,
- 186
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 184,
- 185
- ]
- }
- ],
- "range": [
- 184,
- 186
- ]
}
],
"range": [
@@ -2938,92 +2964,92 @@
154,
156
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 166,
+ 167
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 169,
+ 170
+ ]
+ }
+ ],
+ "range": [
+ 169,
+ 171
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 181,
+ 182
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 184,
+ 185
+ ]
+ }
+ ],
+ "range": [
+ 184,
+ 186
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 192,
+ 193
+ ]
+ }
+ ],
+ "range": [
+ 192,
+ 194
+ ]
+ }
+ ],
+ "range": [
+ 177,
+ 194
+ ]
+ }
+ ],
+ "range": [
+ 162,
+ 194
+ ]
}
],
"range": [
147,
194
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 166,
- 167
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 169,
- 170
- ]
- }
- ],
- "range": [
- 169,
- 171
- ]
- }
- ],
- "range": [
- 162,
- 194
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 181,
- 182
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 184,
- 185
- ]
- }
- ],
- "range": [
- 184,
- 186
- ]
- }
- ],
- "range": [
- 177,
- 194
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 192,
- 193
- ]
- }
- ],
- "range": [
- 192,
- 194
- ]
}
],
"range": [
@@ -3097,9 +3123,19 @@
"filePaths": [
"if-else.js"
],
- "sha1": "a1cc4fcd595d3dc8c9ef506cfef89ef93af156a2",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index 2034be1..6bb0eaa 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1,3 +1,3 @@",
+ "-if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ "+if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "693c7440eaa6e46b057b82f08de419ff9af481bb"
+ "shas": "db2dc88faaeca02e77d4d12d5c72988d460da4aa..5b0fdc4282d1d7326c122766cb51190a2be1b6bb"
}
,{
"testCaseDescription": "javascript-if-else-delete-replacement-test",
@@ -3171,99 +3207,99 @@
22,
28
]
- }
- ],
- "range": [
- 15,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 38,
- 39
- ]
},
{
- "category": "ExpressionStatements",
+ "category": "If",
"children": [
{
"category": "Identifier",
"range": [
- 41,
- 42
+ 38,
+ 39
]
- }
- ],
- "range": [
- 41,
- 43
- ]
- }
- ],
- "range": [
- 34,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 53,
- 54
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
+ },
{
"category": "ExpressionStatements",
"children": [
{
"category": "Identifier",
"range": [
- 58,
- 59
+ 41,
+ 42
]
}
],
"range": [
- 58,
- 60
+ 41,
+ 43
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 53,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 58,
+ 59
+ ]
+ }
+ ],
+ "range": [
+ 58,
+ 60
+ ]
+ }
+ ],
+ "range": [
+ 56,
+ 62
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 68,
+ 69
+ ]
+ }
+ ],
+ "range": [
+ 68,
+ 70
+ ]
+ }
+ ],
+ "range": [
+ 49,
+ 70
]
}
],
"range": [
- 56,
- 62
+ 34,
+ 70
]
}
],
"range": [
- 49,
- 70
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 68,
- 69
- ]
- }
- ],
- "range": [
- 68,
+ 15,
70
]
}
@@ -3346,92 +3382,92 @@
92,
94
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 104,
+ 105
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 107,
+ 108
+ ]
+ }
+ ],
+ "range": [
+ 107,
+ 109
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 119,
+ 120
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 122,
+ 123
+ ]
+ }
+ ],
+ "range": [
+ 122,
+ 124
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 130,
+ 131
+ ]
+ }
+ ],
+ "range": [
+ 130,
+ 132
+ ]
+ }
+ ],
+ "range": [
+ 115,
+ 132
+ ]
+ }
+ ],
+ "range": [
+ 100,
+ 132
+ ]
}
],
"range": [
85,
132
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 104,
- 105
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 107,
- 108
- ]
- }
- ],
- "range": [
- 107,
- 109
- ]
- }
- ],
- "range": [
- 100,
- 132
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 119,
- 120
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 122,
- 123
- ]
- }
- ],
- "range": [
- 122,
- 124
- ]
- }
- ],
- "range": [
- 115,
- 132
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 130,
- 131
- ]
- }
- ],
- "range": [
- 130,
- 132
- ]
}
],
"patch": "delete",
@@ -3512,92 +3548,92 @@
154,
156
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 166,
+ 167
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 169,
+ 170
+ ]
+ }
+ ],
+ "range": [
+ 169,
+ 171
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 181,
+ 182
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 184,
+ 185
+ ]
+ }
+ ],
+ "range": [
+ 184,
+ 186
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 192,
+ 193
+ ]
+ }
+ ],
+ "range": [
+ 192,
+ 194
+ ]
+ }
+ ],
+ "range": [
+ 177,
+ 194
+ ]
+ }
+ ],
+ "range": [
+ 162,
+ 194
+ ]
}
],
"range": [
147,
194
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 166,
- 167
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 169,
- 170
- ]
- }
- ],
- "range": [
- 169,
- 171
- ]
- }
- ],
- "range": [
- 162,
- 194
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 181,
- 182
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 184,
- 185
- ]
- }
- ],
- "range": [
- 184,
- 186
- ]
- }
- ],
- "range": [
- 177,
- 194
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 192,
- 193
- ]
- }
- ],
- "range": [
- 192,
- 194
- ]
}
],
"range": [
@@ -3675,92 +3711,92 @@
22,
24
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 34,
+ 35
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 37,
+ 38
+ ]
+ }
+ ],
+ "range": [
+ 37,
+ 39
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 49,
+ 50
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 52,
+ 53
+ ]
+ }
+ ],
+ "range": [
+ 52,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 60,
+ 61
+ ]
+ }
+ ],
+ "range": [
+ 60,
+ 62
+ ]
+ }
+ ],
+ "range": [
+ 45,
+ 62
+ ]
+ }
+ ],
+ "range": [
+ 30,
+ 62
+ ]
}
],
"range": [
15,
62
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 34,
- 35
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 37,
- 38
- ]
- }
- ],
- "range": [
- 37,
- 39
- ]
- }
- ],
- "range": [
- 30,
- 62
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 49,
- 50
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 52,
- 53
- ]
- }
- ],
- "range": [
- 52,
- 54
- ]
- }
- ],
- "range": [
- 45,
- 62
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 60,
- 61
- ]
- }
- ],
- "range": [
- 60,
- 62
- ]
}
],
"range": [
@@ -3849,99 +3885,99 @@
84,
90
]
- }
- ],
- "range": [
- 77,
- 132
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 100,
- 101
- ]
},
{
- "category": "ExpressionStatements",
+ "category": "If",
"children": [
{
"category": "Identifier",
"range": [
- 103,
- 104
+ 100,
+ 101
]
- }
- ],
- "range": [
- 103,
- 105
- ]
- }
- ],
- "range": [
- 96,
- 132
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 115,
- 116
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
+ },
{
"category": "ExpressionStatements",
"children": [
{
"category": "Identifier",
"range": [
- 120,
- 121
+ 103,
+ 104
]
}
],
"range": [
- 120,
- 122
+ 103,
+ 105
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 115,
+ 116
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 120,
+ 121
+ ]
+ }
+ ],
+ "range": [
+ 120,
+ 122
+ ]
+ }
+ ],
+ "range": [
+ 118,
+ 124
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 130,
+ 131
+ ]
+ }
+ ],
+ "range": [
+ 130,
+ 132
+ ]
+ }
+ ],
+ "range": [
+ 111,
+ 132
]
}
],
"range": [
- 118,
- 124
+ 96,
+ 132
]
}
],
"range": [
- 111,
- 132
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 130,
- 131
- ]
- }
- ],
- "range": [
- 130,
+ 77,
132
]
}
@@ -4018,9 +4054,19 @@
"filePaths": [
"if-else.js"
],
- "sha1": "693c7440eaa6e46b057b82f08de419ff9af481bb",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index 6bb0eaa..e26d6c4 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1,3 +1,2 @@",
+ "-if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o",
+ "-if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ "+if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0d72ea3d00baaa9b5cb0da6d293e21fc2121b39a"
+ "shas": "5b0fdc4282d1d7326c122766cb51190a2be1b6bb..2f737e139adcdbaeeaf780eb49df2b904642b16b"
}
,{
"testCaseDescription": "javascript-if-else-delete-test",
@@ -4083,92 +4129,92 @@
22,
24
]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 34,
+ 35
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 37,
+ 38
+ ]
+ }
+ ],
+ "range": [
+ 37,
+ 39
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 49,
+ 50
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 52,
+ 53
+ ]
+ }
+ ],
+ "range": [
+ 52,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 60,
+ 61
+ ]
+ }
+ ],
+ "range": [
+ 60,
+ 62
+ ]
+ }
+ ],
+ "range": [
+ 45,
+ 62
+ ]
+ }
+ ],
+ "range": [
+ 30,
+ 62
+ ]
}
],
"range": [
15,
62
]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 34,
- 35
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 37,
- 38
- ]
- }
- ],
- "range": [
- 37,
- 39
- ]
- }
- ],
- "range": [
- 30,
- 62
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 49,
- 50
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 52,
- 53
- ]
- }
- ],
- "range": [
- 52,
- 54
- ]
- }
- ],
- "range": [
- 45,
- 62
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 60,
- 61
- ]
- }
- ],
- "range": [
- 60,
- 62
- ]
}
],
"patch": "delete",
@@ -4258,99 +4304,99 @@
84,
90
]
- }
- ],
- "range": [
- 77,
- 132
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 100,
- 101
- ]
},
{
- "category": "ExpressionStatements",
+ "category": "If",
"children": [
{
"category": "Identifier",
"range": [
- 103,
- 104
+ 100,
+ 101
]
- }
- ],
- "range": [
- 103,
- 105
- ]
- }
- ],
- "range": [
- 96,
- 132
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 115,
- 116
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
+ },
{
"category": "ExpressionStatements",
"children": [
{
"category": "Identifier",
"range": [
- 120,
- 121
+ 103,
+ 104
]
}
],
"range": [
- 120,
- 122
+ 103,
+ 105
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 115,
+ 116
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 120,
+ 121
+ ]
+ }
+ ],
+ "range": [
+ 120,
+ 122
+ ]
+ }
+ ],
+ "range": [
+ 118,
+ 124
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 130,
+ 131
+ ]
+ }
+ ],
+ "range": [
+ 130,
+ 132
+ ]
+ }
+ ],
+ "range": [
+ 111,
+ 132
]
}
],
"range": [
- 118,
- 124
+ 96,
+ 132
]
}
],
"range": [
- 111,
- 132
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 130,
- 131
- ]
- }
- ],
- "range": [
- 130,
+ 77,
132
]
}
@@ -4439,99 +4485,99 @@
22,
28
]
- }
- ],
- "range": [
- 15,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 38,
- 39
- ]
},
{
- "category": "ExpressionStatements",
+ "category": "If",
"children": [
{
"category": "Identifier",
"range": [
- 41,
- 42
+ 38,
+ 39
]
- }
- ],
- "range": [
- 41,
- 43
- ]
- }
- ],
- "range": [
- 34,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 53,
- 54
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
+ },
{
"category": "ExpressionStatements",
"children": [
{
"category": "Identifier",
"range": [
- 58,
- 59
+ 41,
+ 42
]
}
],
"range": [
- 58,
- 60
+ 41,
+ 43
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 53,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 58,
+ 59
+ ]
+ }
+ ],
+ "range": [
+ 58,
+ 60
+ ]
+ }
+ ],
+ "range": [
+ 56,
+ 62
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 68,
+ 69
+ ]
+ }
+ ],
+ "range": [
+ 68,
+ 70
+ ]
+ }
+ ],
+ "range": [
+ 49,
+ 70
]
}
],
"range": [
- 56,
- 62
+ 34,
+ 70
]
}
],
"range": [
- 49,
- 70
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 68,
- 69
- ]
- }
- ],
- "range": [
- 68,
+ 15,
70
]
}
@@ -4607,9 +4653,17 @@
"filePaths": [
"if-else.js"
],
- "sha1": "0d72ea3d00baaa9b5cb0da6d293e21fc2121b39a",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index e26d6c4..1a55d0b 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1,2 +1 @@",
+ "-if (x) y; else if (a) b; else if (c) d; else if (e) f; else g",
+ " if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "25cba19f0b86fed61180b2a12a48b1dca15e1384"
+ "shas": "2f737e139adcdbaeeaf780eb49df2b904642b16b..168b06d356ffd180f13ad8f9c26fa0ed8adfc3eb"
}
,{
"testCaseDescription": "javascript-if-else-delete-rest-test",
@@ -4681,99 +4735,99 @@
22,
28
]
- }
- ],
- "range": [
- 15,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 38,
- 39
- ]
},
{
- "category": "ExpressionStatements",
+ "category": "If",
"children": [
{
"category": "Identifier",
"range": [
- 41,
- 42
+ 38,
+ 39
]
- }
- ],
- "range": [
- 41,
- 43
- ]
- }
- ],
- "range": [
- 34,
- 70
- ]
- },
- {
- "category": "If",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 53,
- 54
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
+ },
{
"category": "ExpressionStatements",
"children": [
{
"category": "Identifier",
"range": [
- 58,
- 59
+ 41,
+ 42
]
}
],
"range": [
- 58,
- 60
+ 41,
+ 43
+ ]
+ },
+ {
+ "category": "If",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 53,
+ 54
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 58,
+ 59
+ ]
+ }
+ ],
+ "range": [
+ 58,
+ 60
+ ]
+ }
+ ],
+ "range": [
+ 56,
+ 62
+ ]
+ },
+ {
+ "category": "ExpressionStatements",
+ "children": [
+ {
+ "category": "Identifier",
+ "range": [
+ 68,
+ 69
+ ]
+ }
+ ],
+ "range": [
+ 68,
+ 70
+ ]
+ }
+ ],
+ "range": [
+ 49,
+ 70
]
}
],
"range": [
- 56,
- 62
+ 34,
+ 70
]
}
],
"range": [
- 49,
- 70
- ]
- },
- {
- "category": "ExpressionStatements",
- "children": [
- {
- "category": "Identifier",
- "range": [
- 68,
- 69
- ]
- }
- ],
- "range": [
- 68,
+ 15,
70
]
}
@@ -4833,7 +4887,14 @@
"filePaths": [
"if-else.js"
],
- "sha1": "25cba19f0b86fed61180b2a12a48b1dca15e1384",
+ "patch": [
+ "diff --git a/if-else.js b/if-else.js",
+ "index 1a55d0b..e69de29 100644",
+ "--- a/if-else.js",
+ "+++ b/if-else.js",
+ "@@ -1 +0,0 @@",
+ "-if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "57942e93fabda394bc01cee76c0313089454e309"
+ "shas": "168b06d356ffd180f13ad8f9c26fa0ed8adfc3eb..c32361c31b256ea32638cead8a9639d9d3bb55d4"
}]
diff --git a/test/corpus/json/javascript/if.json b/test/corpus/json/javascript/if.json
index 89973acd4..8dcfac301 100644
--- a/test/corpus/json/javascript/if.json
+++ b/test/corpus/json/javascript/if.json
@@ -115,9 +115,16 @@
"filePaths": [
"if.js"
],
- "sha1": "f6609017b201ccacdd96341f8be7440ed0396418",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index e69de29..52d4b4f 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -0,0 +1 @@",
+ "+if (x) { log(y); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "17fac07d795c26d5134ff41ddd477e52433845a8"
+ "shas": "1414e435bed741828bc662b2617b65f006198115..f925589600daebd1c530948026f8ca735c3d2295"
}
,{
"testCaseDescription": "javascript-if-replacement-insert-test",
@@ -518,9 +525,18 @@
"filePaths": [
"if.js"
],
- "sha1": "17fac07d795c26d5134ff41ddd477e52433845a8",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index 52d4b4f..ae4ee32 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1 +1,3 @@",
+ "+if (a.b) { log(c); d; }",
+ "+if (x) { log(y); }",
+ " if (x) { log(y); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "911d1f22fec27d977cb2b723c0db868de665fb89"
+ "shas": "f925589600daebd1c530948026f8ca735c3d2295..953b51e76de53d368e5aaeedb84b46cec9e2ac83"
}
,{
"testCaseDescription": "javascript-if-delete-insert-test",
@@ -1073,9 +1089,19 @@
"filePaths": [
"if.js"
],
- "sha1": "911d1f22fec27d977cb2b723c0db868de665fb89",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index ae4ee32..df55832 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1,3 +1,3 @@",
+ "-if (a.b) { log(c); d; }",
+ "+if (x) { log(y); }",
+ " if (x) { log(y); }",
+ " if (x) { log(y); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "84d8877b6c823ebd388caa98883aea87e020c1b2"
+ "shas": "953b51e76de53d368e5aaeedb84b46cec9e2ac83..bed63a4361da46793cece7c3f1370d78fd311348"
}
,{
"testCaseDescription": "javascript-if-replacement-test",
@@ -1628,9 +1654,19 @@
"filePaths": [
"if.js"
],
- "sha1": "84d8877b6c823ebd388caa98883aea87e020c1b2",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index df55832..ae4ee32 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1,3 +1,3 @@",
+ "-if (x) { log(y); }",
+ "+if (a.b) { log(c); d; }",
+ " if (x) { log(y); }",
+ " if (x) { log(y); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c74eae90461b324c7a660df1882ccf08d6a8af37"
+ "shas": "bed63a4361da46793cece7c3f1370d78fd311348..1d1e851c9148d9e8b3e8d6d7ff8e46412e33b7f5"
}
,{
"testCaseDescription": "javascript-if-delete-replacement-test",
@@ -2142,9 +2178,19 @@
"filePaths": [
"if.js"
],
- "sha1": "c74eae90461b324c7a660df1882ccf08d6a8af37",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index ae4ee32..38b83ef 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1,3 +1,2 @@",
+ "-if (a.b) { log(c); d; }",
+ "-if (x) { log(y); }",
+ " if (x) { log(y); }",
+ "+if (a.b) { log(c); d; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4be85c44602984a459303b6dfbbdc106893cff03"
+ "shas": "1d1e851c9148d9e8b3e8d6d7ff8e46412e33b7f5..bfee3fdff9441afb2bfac9650139f2fe3517d1fb"
}
,{
"testCaseDescription": "javascript-if-delete-test",
@@ -2498,9 +2544,17 @@
"filePaths": [
"if.js"
],
- "sha1": "4be85c44602984a459303b6dfbbdc106893cff03",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index 38b83ef..f67163b 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1,2 +1 @@",
+ "-if (x) { log(y); }",
+ " if (a.b) { log(c); d; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4a963890501b7fd3668285ac04cc911f3d42aee6"
+ "shas": "bfee3fdff9441afb2bfac9650139f2fe3517d1fb..199fb9c9073c557c909722b9586409dc8ca619d7"
}
,{
"testCaseDescription": "javascript-if-delete-rest-test",
@@ -2651,7 +2705,14 @@
"filePaths": [
"if.js"
],
- "sha1": "4a963890501b7fd3668285ac04cc911f3d42aee6",
+ "patch": [
+ "diff --git a/if.js b/if.js",
+ "index f67163b..e69de29 100644",
+ "--- a/if.js",
+ "+++ b/if.js",
+ "@@ -1 +0,0 @@",
+ "-if (a.b) { log(c); d; }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0d04a39119475382fd1b236c00355a271286be24"
+ "shas": "199fb9c9073c557c909722b9586409dc8ca619d7..a7c68af9b8e2a95ea64781f7701d616d9831d54b"
}]
diff --git a/test/corpus/json/javascript/import.json b/test/corpus/json/javascript/import.json
index bef36c875..377430ef4 100644
--- a/test/corpus/json/javascript/import.json
+++ b/test/corpus/json/javascript/import.json
@@ -57,7 +57,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -439,7 +439,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -555,9 +555,23 @@
"filePaths": [
"import.js"
],
- "sha1": "81765d4b8506ea59264b4bdc0c5b8c2c78a0a1a2",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index e69de29..491cb15 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -0,0 +1,8 @@",
+ "+import defaultMember from \"foo\";",
+ "+import * as name from \"aardvark\";",
+ "+import { member } from \"ant\";",
+ "+import { member1 , member2 } from \"antelope\";",
+ "+import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "+import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "+import defaultMember, * as name from \"alligator\";",
+ "+import \"arctic-tern\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7764a1ed5e5cadc806e7c7d90c914646836fc246"
+ "shas": "81a41e72cb6728374f1f2c700f5656622f0966ec..7797a9819842490dcdc548a3dae02898cd7b1939"
}
,{
"testCaseDescription": "javascript-import-replacement-insert-test",
@@ -618,7 +632,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -1000,7 +1014,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -1137,7 +1151,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -1519,7 +1533,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -1697,7 +1711,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -1748,7 +1762,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -2434,7 +2448,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -2492,7 +2506,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -2658,9 +2672,34 @@
"filePaths": [
"import.js"
],
- "sha1": "7764a1ed5e5cadc806e7c7d90c914646836fc246",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index 491cb15..045c536 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,3 +1,19 @@",
+ "+import defaultMember from \"babirusa\";",
+ "+import * as otherName from \"baboon\";",
+ "+import { element } from \"badger\";",
+ "+import { element1 , element2 } from \"bald-eagle\";",
+ "+import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "+import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "+import defaultMember, * as element from \"barbet\";",
+ "+import \"basilisk\";",
+ "+import defaultMember from \"foo\";",
+ "+import * as name from \"aardvark\";",
+ "+import { member } from \"ant\";",
+ "+import { member1 , member2 } from \"antelope\";",
+ "+import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "+import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "+import defaultMember, * as name from \"alligator\";",
+ "+import \"arctic-tern\";",
+ " import defaultMember from \"foo\";",
+ " import * as name from \"aardvark\";",
+ " import { member } from \"ant\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "573862dc0acbd88e67e2bdb92045820677d5b308"
+ "shas": "7797a9819842490dcdc548a3dae02898cd7b1939..4f93e4a12682c20523777c8ff21c23637b93b2c3"
}
,{
"testCaseDescription": "javascript-import-delete-insert-test",
@@ -2764,7 +2803,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -2817,7 +2856,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -3261,7 +3300,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -3580,7 +3619,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -3796,7 +3835,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -3847,7 +3886,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -4533,7 +4572,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -4591,7 +4630,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -4802,7 +4841,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -4853,7 +4892,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -5539,7 +5578,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -5597,7 +5636,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -5763,9 +5802,34 @@
"filePaths": [
"import.js"
],
- "sha1": "573862dc0acbd88e67e2bdb92045820677d5b308",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index 045c536..cbad5a4 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,11 +1,11 @@",
+ "-import defaultMember from \"babirusa\";",
+ "-import * as otherName from \"baboon\";",
+ "-import { element } from \"badger\";",
+ "-import { element1 , element2 } from \"bald-eagle\";",
+ "-import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "-import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "-import defaultMember, * as element from \"barbet\";",
+ "-import \"basilisk\";",
+ "+import defaultMember from \"foo\";",
+ "+import * as name from \"aardvark\";",
+ "+import { member } from \"ant\";",
+ "+import { member1 , member2 } from \"antelope\";",
+ "+import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "+import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "+import defaultMember, * as name from \"alligator\";",
+ "+import \"arctic-tern\";",
+ " import defaultMember from \"foo\";",
+ " import * as name from \"aardvark\";",
+ " import { member } from \"ant\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "dcdfd23a76fd5d4401d602c8d689f4881882f910"
+ "shas": "4f93e4a12682c20523777c8ff21c23637b93b2c3..1a2c0ee4f2d6d47acc0e0b75adfd77412cdb5208"
}
,{
"testCaseDescription": "javascript-import-replacement-test",
@@ -5869,7 +5933,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -5922,7 +5986,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -6366,7 +6430,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -6685,7 +6749,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -6901,7 +6965,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -6952,7 +7016,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -7638,7 +7702,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -7696,7 +7760,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -7907,7 +7971,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -7958,7 +8022,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -8644,7 +8708,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -8702,7 +8766,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -8868,9 +8932,34 @@
"filePaths": [
"import.js"
],
- "sha1": "dcdfd23a76fd5d4401d602c8d689f4881882f910",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index cbad5a4..045c536 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,11 +1,11 @@",
+ "-import defaultMember from \"foo\";",
+ "-import * as name from \"aardvark\";",
+ "-import { member } from \"ant\";",
+ "-import { member1 , member2 } from \"antelope\";",
+ "-import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "-import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "-import defaultMember, * as name from \"alligator\";",
+ "-import \"arctic-tern\";",
+ "+import defaultMember from \"babirusa\";",
+ "+import * as otherName from \"baboon\";",
+ "+import { element } from \"badger\";",
+ "+import { element1 , element2 } from \"bald-eagle\";",
+ "+import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "+import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "+import defaultMember, * as element from \"barbet\";",
+ "+import \"basilisk\";",
+ " import defaultMember from \"foo\";",
+ " import * as name from \"aardvark\";",
+ " import { member } from \"ant\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0723e121a3ee09cd5f62dec4af4e33a7d700c977"
+ "shas": "1a2c0ee4f2d6d47acc0e0b75adfd77412cdb5208..9cee417f36dc72559f8005d43c1c64e38d14b260"
}
,{
"testCaseDescription": "javascript-import-delete-replacement-test",
@@ -8931,7 +9020,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -9313,7 +9402,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -9450,7 +9539,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -9832,7 +9921,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -10010,7 +10099,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -10061,7 +10150,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -10747,7 +10836,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -10805,7 +10894,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -10975,7 +11064,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -11357,7 +11446,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -11490,9 +11579,46 @@
"filePaths": [
"import.js"
],
- "sha1": "0723e121a3ee09cd5f62dec4af4e33a7d700c977",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index 045c536..873ff75 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,19 +1,3 @@",
+ "-import defaultMember from \"babirusa\";",
+ "-import * as otherName from \"baboon\";",
+ "-import { element } from \"badger\";",
+ "-import { element1 , element2 } from \"bald-eagle\";",
+ "-import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "-import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "-import defaultMember, * as element from \"barbet\";",
+ "-import \"basilisk\";",
+ "-import defaultMember from \"foo\";",
+ "-import * as name from \"aardvark\";",
+ "-import { member } from \"ant\";",
+ "-import { member1 , member2 } from \"antelope\";",
+ "-import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "-import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "-import defaultMember, * as name from \"alligator\";",
+ "-import \"arctic-tern\";",
+ " import defaultMember from \"foo\";",
+ " import * as name from \"aardvark\";",
+ " import { member } from \"ant\";",
+ "@@ -22,3 +6,11 @@ import { member1 , member2 as alias2 } from \"ant-eater\";",
+ " import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ " import defaultMember, * as name from \"alligator\";",
+ " import \"arctic-tern\";",
+ "+import defaultMember from \"babirusa\";",
+ "+import * as otherName from \"baboon\";",
+ "+import { element } from \"badger\";",
+ "+import { element1 , element2 } from \"bald-eagle\";",
+ "+import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "+import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "+import defaultMember, * as element from \"barbet\";",
+ "+import \"basilisk\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "93209ee02dddd72a77185a98cec4286530c3e0c8"
+ "shas": "9cee417f36dc72559f8005d43c1c64e38d14b260..04525879004b8577a357fe3fa2c7c5937218f3f4"
}
,{
"testCaseDescription": "javascript-import-delete-test",
@@ -11553,7 +11679,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -11935,7 +12061,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -12113,7 +12239,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -12164,7 +12290,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -12850,7 +12976,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -12908,7 +13034,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -13074,9 +13200,26 @@
"filePaths": [
"import.js"
],
- "sha1": "93209ee02dddd72a77185a98cec4286530c3e0c8",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index 873ff75..db72339 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,11 +1,3 @@",
+ "-import defaultMember from \"foo\";",
+ "-import * as name from \"aardvark\";",
+ "-import { member } from \"ant\";",
+ "-import { member1 , member2 } from \"antelope\";",
+ "-import { member1 , member2 as alias2 } from \"ant-eater\";",
+ "-import defaultMember, { member1, member2 as alias2 } from \"anaconda\";",
+ "-import defaultMember, * as name from \"alligator\";",
+ "-import \"arctic-tern\";",
+ " import defaultMember from \"babirusa\";",
+ " import * as otherName from \"baboon\";",
+ " import { element } from \"badger\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "702f5e0c40d63fdedd28a48286bd9dda6280ead2"
+ "shas": "04525879004b8577a357fe3fa2c7c5937218f3f4..31410516cd8aa6df7e993b64253cb523aab15729"
}
,{
"testCaseDescription": "javascript-import-delete-rest-test",
@@ -13137,7 +13280,7 @@
"category": "Import",
"children": [
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -13519,7 +13662,7 @@
]
},
{
- "category": "NamespaceImport",
+ "category": "namespace_import",
"children": [
{
"category": "Identifier",
@@ -13635,7 +13778,21 @@
"filePaths": [
"import.js"
],
- "sha1": "702f5e0c40d63fdedd28a48286bd9dda6280ead2",
+ "patch": [
+ "diff --git a/import.js b/import.js",
+ "index db72339..e69de29 100644",
+ "--- a/import.js",
+ "+++ b/import.js",
+ "@@ -1,8 +0,0 @@",
+ "-import defaultMember from \"babirusa\";",
+ "-import * as otherName from \"baboon\";",
+ "-import { element } from \"badger\";",
+ "-import { element1 , element2 } from \"bald-eagle\";",
+ "-import { element1 , element2 as elementAlias2 } from \"bandicoot\";",
+ "-import defaultMember, { element1, element2 as elementAlias2 } from \"banteng\";",
+ "-import defaultMember, * as element from \"barbet\";",
+ "-import \"basilisk\";"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "22db42187b94dca9b3ba3ce80361c21a8b48b777"
+ "shas": "31410516cd8aa6df7e993b64253cb523aab15729..0bb74af8eede739c6d9a6b79a13e61263d3c52e6"
}]
diff --git a/test/corpus/json/javascript/math-assignment-operator.json b/test/corpus/json/javascript/math-assignment-operator.json
index a5337184d..2d0d1f80a 100644
--- a/test/corpus/json/javascript/math-assignment-operator.json
+++ b/test/corpus/json/javascript/math-assignment-operator.json
@@ -90,9 +90,16 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "71f81ec7bab5350490d3ff7f2444799df17938ba",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index e69de29..7150d6e 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -0,0 +1 @@",
+ "+x += 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e1fcc6e84011e22cd17ffedaf313bd5fe8f96701"
+ "shas": "2dd315197d728e8efdfc502c8ec48dac3ee8a4b7..ded203079c60a3d7a343120c4c5a54079dd4340e"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test",
@@ -361,9 +368,18 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "e1fcc6e84011e22cd17ffedaf313bd5fe8f96701",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index 7150d6e..0bf97e7 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1 +1,3 @@",
+ "+x += 2;",
+ "+x += 1;",
+ " x += 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ad2641c99ae3cb2ddf8eec508ac21b917f0c2dee"
+ "shas": "ded203079c60a3d7a343120c4c5a54079dd4340e..ab4c64432f01363febab14a118751ced86cbede9"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-insert-test",
@@ -734,9 +750,19 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "ad2641c99ae3cb2ddf8eec508ac21b917f0c2dee",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index 0bf97e7..ad04937 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-x += 2;",
+ "+x += 1;",
+ " x += 1;",
+ " x += 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d141c1857e9c0c7fd467b25c2de1796ae2f3bd83"
+ "shas": "ab4c64432f01363febab14a118751ced86cbede9..c631f771b1428cf1a28dc4db4d00252aa24b22fe"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-replacement-test",
@@ -1107,9 +1133,19 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "d141c1857e9c0c7fd467b25c2de1796ae2f3bd83",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index ad04937..0bf97e7 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-x += 1;",
+ "+x += 2;",
+ " x += 1;",
+ " x += 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "22bc438d17c00f0616cd58900a50390d90a928f5"
+ "shas": "c631f771b1428cf1a28dc4db4d00252aa24b22fe..6f08c08ae092e52ef599812163e6b8b39330ab63"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test",
@@ -1432,9 +1468,19 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "22bc438d17c00f0616cd58900a50390d90a928f5",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index 0bf97e7..7127545 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-x += 2;",
+ "-x += 1;",
+ " x += 1;",
+ "+x += 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fa10fe52dc2d0ecf740ac756b526c4174c1cf160"
+ "shas": "6f08c08ae092e52ef599812163e6b8b39330ab63..b7d905cc763b31035f76fda7ac7f3b48f8df1154"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-test",
@@ -1649,9 +1695,17 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "fa10fe52dc2d0ecf740ac756b526c4174c1cf160",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index 7127545..94d1472 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1,2 +1 @@",
+ "-x += 1;",
+ " x += 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ac44e36dfe0afdaed22058f4cbd8afab7838db7d"
+ "shas": "b7d905cc763b31035f76fda7ac7f3b48f8df1154..634f52893f90b01720432e519a9feb7c07c26012"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-rest-test",
@@ -1745,7 +1799,14 @@
"filePaths": [
"math-assignment-operator.js"
],
- "sha1": "ac44e36dfe0afdaed22058f4cbd8afab7838db7d",
+ "patch": [
+ "diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
+ "index 94d1472..e69de29 100644",
+ "--- a/math-assignment-operator.js",
+ "+++ b/math-assignment-operator.js",
+ "@@ -1 +0,0 @@",
+ "-x += 2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8f8309aab5b170620dd56a95dde3a0a1c4307c68"
+ "shas": "634f52893f90b01720432e519a9feb7c07c26012..8dd4d424eeae076b657c04fb290058c4635ae818"
}]
diff --git a/test/corpus/json/javascript/math-operator.json b/test/corpus/json/javascript/math-operator.json
index 7c1ade230..81ed7425a 100644
--- a/test/corpus/json/javascript/math-operator.json
+++ b/test/corpus/json/javascript/math-operator.json
@@ -138,9 +138,16 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "95e0c499ee3b410bdb68dc5dfdc10f6779f9cc5e",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index e69de29..0344667 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -0,0 +1 @@",
+ "+i + j * 3 - j % 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "443da40886cb1866b1d657ceceab618352be8675"
+ "shas": "349ec3f8639b7b854f6fcfdaaf8e2ef63c05fef7..c10213a914cc4c581935c845587b1615f782b23d"
}
,{
"testCaseDescription": "javascript-math-operator-replacement-insert-test",
@@ -601,9 +608,18 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "443da40886cb1866b1d657ceceab618352be8675",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index 0344667..79f5f20 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1 +1,3 @@",
+ "+i + j * 2 - j % 4;",
+ "+i + j * 3 - j % 5;",
+ " i + j * 3 - j % 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7312c61f5d5ee29c95555b42f7d11f60cd344fec"
+ "shas": "c10213a914cc4c581935c845587b1615f782b23d..8d0e873b6e585bc5d038b3597e50375979bab9d7"
}
,{
"testCaseDescription": "javascript-math-operator-delete-insert-test",
@@ -1264,9 +1280,19 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "7312c61f5d5ee29c95555b42f7d11f60cd344fec",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index 79f5f20..284561c 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i + j * 2 - j % 4;",
+ "+i + j * 3 - j % 5;",
+ " i + j * 3 - j % 5;",
+ " i + j * 3 - j % 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9507cc1561104c8afe3e064ebc6126d48f016736"
+ "shas": "8d0e873b6e585bc5d038b3597e50375979bab9d7..410a2f6f9d81e855cad2997c46445446d9a969d3"
}
,{
"testCaseDescription": "javascript-math-operator-replacement-test",
@@ -1927,9 +1953,19 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "9507cc1561104c8afe3e064ebc6126d48f016736",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index 284561c..79f5f20 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-i + j * 3 - j % 5;",
+ "+i + j * 2 - j % 4;",
+ " i + j * 3 - j % 5;",
+ " i + j * 3 - j % 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "56fd5e9fe2c66f3f5299a59c5dcef92a2e25cd37"
+ "shas": "410a2f6f9d81e855cad2997c46445446d9a969d3..2682d71eb0c050080c252a74b5086466a18fbeac"
}
,{
"testCaseDescription": "javascript-math-operator-delete-replacement-test",
@@ -2492,9 +2528,19 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "56fd5e9fe2c66f3f5299a59c5dcef92a2e25cd37",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index 79f5f20..d1055f7 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-i + j * 2 - j % 4;",
+ "-i + j * 3 - j % 5;",
+ " i + j * 3 - j % 5;",
+ "+i + j * 2 - j % 4;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a934414df2234ddfb241b47bd04e8acc77a85e75"
+ "shas": "2682d71eb0c050080c252a74b5086466a18fbeac..e94c4f98fb944fbc75a8f45d35f143b51d1eb642"
}
,{
"testCaseDescription": "javascript-math-operator-delete-test",
@@ -2853,9 +2899,17 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "a934414df2234ddfb241b47bd04e8acc77a85e75",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index d1055f7..79ba2b3 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1,2 +1 @@",
+ "-i + j * 3 - j % 5;",
+ " i + j * 2 - j % 4;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "423a0a8085dc2ccba9e0a11c8c321b53672d524e"
+ "shas": "e94c4f98fb944fbc75a8f45d35f143b51d1eb642..946717e49735f8b580f7b162468c366784e6678d"
}
,{
"testCaseDescription": "javascript-math-operator-delete-rest-test",
@@ -2997,7 +3051,14 @@
"filePaths": [
"math-operator.js"
],
- "sha1": "423a0a8085dc2ccba9e0a11c8c321b53672d524e",
+ "patch": [
+ "diff --git a/math-operator.js b/math-operator.js",
+ "index 79ba2b3..e69de29 100644",
+ "--- a/math-operator.js",
+ "+++ b/math-operator.js",
+ "@@ -1 +0,0 @@",
+ "-i + j * 2 - j % 4;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "714e5a0dfd44d739d9669ab32c1f32160436e5a2"
+ "shas": "946717e49735f8b580f7b162468c366784e6678d..b0194f4ccae027de9b6fbbc4ceefe070cf51555c"
}]
diff --git a/test/corpus/json/javascript/member-access-assignment.json b/test/corpus/json/javascript/member-access-assignment.json
index 9cacd2365..e31a02e15 100644
--- a/test/corpus/json/javascript/member-access-assignment.json
+++ b/test/corpus/json/javascript/member-access-assignment.json
@@ -106,9 +106,16 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "48190229aaa2c5d5ca3796814538a309e3b261d4",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index e69de29..7a99e30 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -0,0 +1 @@",
+ "+y.x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "453cf1754f40593356fef8fca60e37b46798c1bb"
+ "shas": "30a517ace94526eae9f09618d7cc587cdbb96c25..8d4dfc6dee6848d963a1ae274414a21efda49931"
}
,{
"testCaseDescription": "javascript-member-access-assignment-replacement-insert-test",
@@ -441,9 +448,18 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "453cf1754f40593356fef8fca60e37b46798c1bb",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 7a99e30..3204006 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1 +1,3 @@",
+ "+y.x = 1;",
+ "+y.x = 0;",
+ " y.x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a6c204d7a1b542ce75a1e06a8d95b63a3e0cc9ac"
+ "shas": "8d4dfc6dee6848d963a1ae274414a21efda49931..85fb25af4dc9beca3e862fec80f2212cb67e51a8"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-insert-test",
@@ -910,9 +926,19 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "a6c204d7a1b542ce75a1e06a8d95b63a3e0cc9ac",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 3204006..94893a3 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-y.x = 1;",
+ "+y.x = 0;",
+ " y.x = 0;",
+ " y.x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5f6177a9c5b4deec2c6c713f4f8dbd05c9a90f41"
+ "shas": "85fb25af4dc9beca3e862fec80f2212cb67e51a8..20e1b9fe5bd2d81f12abfc191d986ef7fcc86401"
}
,{
"testCaseDescription": "javascript-member-access-assignment-replacement-test",
@@ -1379,9 +1405,19 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "5f6177a9c5b4deec2c6c713f4f8dbd05c9a90f41",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 94893a3..3204006 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-y.x = 0;",
+ "+y.x = 1;",
+ " y.x = 0;",
+ " y.x = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c4611d75f2d4f08833e092f4297f0f259c09ef4c"
+ "shas": "20e1b9fe5bd2d81f12abfc191d986ef7fcc86401..0a32ed61310da85bb560f6fe0466714dfb0623f5"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-replacement-test",
@@ -1784,9 +1820,19 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "c4611d75f2d4f08833e092f4297f0f259c09ef4c",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 3204006..8d78a24 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1,3 +1,2 @@",
+ "-y.x = 1;",
+ "-y.x = 0;",
+ " y.x = 0;",
+ "+y.x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "85c4873bfe30243574ad96c6fc0b796fcd49fa70"
+ "shas": "0a32ed61310da85bb560f6fe0466714dfb0623f5..8906b689174ac6fdae79acf100face3eb283fadd"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-test",
@@ -2049,9 +2095,17 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "85c4873bfe30243574ad96c6fc0b796fcd49fa70",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 8d78a24..799018d 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1,2 +1 @@",
+ "-y.x = 0;",
+ " y.x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3661ffe82cd5f0e93152cad649e3e2e2d90e4474"
+ "shas": "8906b689174ac6fdae79acf100face3eb283fadd..6b8df6e5c3cb67d6c14497e03fbc3f2fbb850f95"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-rest-test",
@@ -2161,7 +2215,14 @@
"filePaths": [
"member-access-assignment.js"
],
- "sha1": "3661ffe82cd5f0e93152cad649e3e2e2d90e4474",
+ "patch": [
+ "diff --git a/member-access-assignment.js b/member-access-assignment.js",
+ "index 799018d..e69de29 100644",
+ "--- a/member-access-assignment.js",
+ "+++ b/member-access-assignment.js",
+ "@@ -1 +0,0 @@",
+ "-y.x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2984e6c47cb68c823069ad8467e3f43d0b833207"
+ "shas": "6b8df6e5c3cb67d6c14497e03fbc3f2fbb850f95..6a942b8c8b6674795040d75810b847dd6dbf37e4"
}]
diff --git a/test/corpus/json/javascript/member-access.json b/test/corpus/json/javascript/member-access.json
index 2bbe05b8e..64690bf59 100644
--- a/test/corpus/json/javascript/member-access.json
+++ b/test/corpus/json/javascript/member-access.json
@@ -90,9 +90,16 @@
"filePaths": [
"member-access.js"
],
- "sha1": "a816d0383b93d78bf467c1afad387fafe01c3111",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index e69de29..3c837c9 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -0,0 +1 @@",
+ "+x.someProperty;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "07ce317c24188e7c5b3a30bf4e85ecae2a80ca87"
+ "shas": "6bb7b92e6660b4bea6500b17891e6215571694a1..a7e9f12709231169ce940b7b5adddb8b700c4740"
}
,{
"testCaseDescription": "javascript-member-access-replacement-insert-test",
@@ -361,9 +368,18 @@
"filePaths": [
"member-access.js"
],
- "sha1": "07ce317c24188e7c5b3a30bf4e85ecae2a80ca87",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 3c837c9..858131a 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1 +1,3 @@",
+ "+x.someOtherProperty",
+ "+x.someProperty;",
+ " x.someProperty;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a8f66d16ff50e27be46da0c438cf697f0bb21347"
+ "shas": "a7e9f12709231169ce940b7b5adddb8b700c4740..8a2a90b5c78a4271528ba0098926b1309345cd81"
}
,{
"testCaseDescription": "javascript-member-access-delete-insert-test",
@@ -734,9 +750,19 @@
"filePaths": [
"member-access.js"
],
- "sha1": "a8f66d16ff50e27be46da0c438cf697f0bb21347",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 858131a..5ed8a8d 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1,3 +1,3 @@",
+ "-x.someOtherProperty",
+ "+x.someProperty;",
+ " x.someProperty;",
+ " x.someProperty;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "60817f8e436ec95656c3a073de32ae6ad339f8b8"
+ "shas": "8a2a90b5c78a4271528ba0098926b1309345cd81..b3e91ac2bb642a9f673811cf0f81464baa0d5107"
}
,{
"testCaseDescription": "javascript-member-access-replacement-test",
@@ -1107,9 +1133,19 @@
"filePaths": [
"member-access.js"
],
- "sha1": "60817f8e436ec95656c3a073de32ae6ad339f8b8",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 5ed8a8d..858131a 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1,3 +1,3 @@",
+ "-x.someProperty;",
+ "+x.someOtherProperty",
+ " x.someProperty;",
+ " x.someProperty;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0404cbe6cc21a5386f60b28539ef9fe05643b170"
+ "shas": "b3e91ac2bb642a9f673811cf0f81464baa0d5107..a840fc931f382340c5556c4189d2d1794ccc11dd"
}
,{
"testCaseDescription": "javascript-member-access-delete-replacement-test",
@@ -1432,9 +1468,19 @@
"filePaths": [
"member-access.js"
],
- "sha1": "0404cbe6cc21a5386f60b28539ef9fe05643b170",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 858131a..81f5f46 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1,3 +1,2 @@",
+ "-x.someOtherProperty",
+ "-x.someProperty;",
+ " x.someProperty;",
+ "+x.someOtherProperty"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6371c8367e8925538f32c7cd4bb3d5dbfd67fb0e"
+ "shas": "a840fc931f382340c5556c4189d2d1794ccc11dd..162904a6f6d643b66a5f4b844ba2e228b7dc6c5e"
}
,{
"testCaseDescription": "javascript-member-access-delete-test",
@@ -1649,9 +1695,17 @@
"filePaths": [
"member-access.js"
],
- "sha1": "6371c8367e8925538f32c7cd4bb3d5dbfd67fb0e",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 81f5f46..8329c77 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1,2 +1 @@",
+ "-x.someProperty;",
+ " x.someOtherProperty"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6a53a985f2fece8768d4b40e67c3e7d37f49a3d5"
+ "shas": "162904a6f6d643b66a5f4b844ba2e228b7dc6c5e..66de6fe8153911bdce9e1e49b303c1e0fa6f3df9"
}
,{
"testCaseDescription": "javascript-member-access-delete-rest-test",
@@ -1745,7 +1799,14 @@
"filePaths": [
"member-access.js"
],
- "sha1": "6a53a985f2fece8768d4b40e67c3e7d37f49a3d5",
+ "patch": [
+ "diff --git a/member-access.js b/member-access.js",
+ "index 8329c77..e69de29 100644",
+ "--- a/member-access.js",
+ "+++ b/member-access.js",
+ "@@ -1 +0,0 @@",
+ "-x.someOtherProperty"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "287b6fa60bf503572cbcddbf84c46e81f3f4008c"
+ "shas": "66de6fe8153911bdce9e1e49b303c1e0fa6f3df9..75ba258ab370ff0efecb47f5f6a2f6a9968e9b8d"
}]
diff --git a/test/corpus/json/javascript/method-call.json b/test/corpus/json/javascript/method-call.json
index 9486cbcea..7d2d6271b 100644
--- a/test/corpus/json/javascript/method-call.json
+++ b/test/corpus/json/javascript/method-call.json
@@ -104,9 +104,16 @@
"filePaths": [
"method-call.js"
],
- "sha1": "1011f24f71bd4ec75766ffbe5d5a27d625dabc58",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index e69de29..07ab90c 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -0,0 +1 @@",
+ "+object.someMethod(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8c8c6db2489fdb60319c45247ec81fc673013ed2"
+ "shas": "7aca49a04758f43f9e7c909ee616f33c18cf0e27..a391db61c291e9652b50630df1819b83df83ffea"
}
,{
"testCaseDescription": "javascript-method-call-replacement-insert-test",
@@ -431,9 +438,18 @@
"filePaths": [
"method-call.js"
],
- "sha1": "8c8c6db2489fdb60319c45247ec81fc673013ed2",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index 07ab90c..9341e17 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1 +1,3 @@",
+ "+object.someMethod(arg1, \"arg3\");",
+ "+object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2b25b3a837d54445ad73bf1f96830097063f02e5"
+ "shas": "a391db61c291e9652b50630df1819b83df83ffea..8a52922fc1e9800afafa4c5bb1bd7c6bf8bc1673"
}
,{
"testCaseDescription": "javascript-method-call-delete-insert-test",
@@ -888,9 +904,19 @@
"filePaths": [
"method-call.js"
],
- "sha1": "2b25b3a837d54445ad73bf1f96830097063f02e5",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index 9341e17..f6ada2d 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-object.someMethod(arg1, \"arg3\");",
+ "+object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2a4bfcfb5d0dbb10b7defd87f552ef03f5741ae2"
+ "shas": "8a52922fc1e9800afafa4c5bb1bd7c6bf8bc1673..af43a2e5f963ea29cb4bbef3df5d610dfb0dd6c4"
}
,{
"testCaseDescription": "javascript-method-call-replacement-test",
@@ -1345,9 +1371,19 @@
"filePaths": [
"method-call.js"
],
- "sha1": "2a4bfcfb5d0dbb10b7defd87f552ef03f5741ae2",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index f6ada2d..9341e17 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1,3 +1,3 @@",
+ "-object.someMethod(arg1, \"arg2\");",
+ "+object.someMethod(arg1, \"arg3\");",
+ " object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg2\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "05f43c5f9431d13afc45f2f3086b603fd176c82b"
+ "shas": "af43a2e5f963ea29cb4bbef3df5d610dfb0dd6c4..51076f4ed7a3e7277b2d21eaecc04fe0ac703d33"
}
,{
"testCaseDescription": "javascript-method-call-delete-replacement-test",
@@ -1740,9 +1776,19 @@
"filePaths": [
"method-call.js"
],
- "sha1": "05f43c5f9431d13afc45f2f3086b603fd176c82b",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index 9341e17..894dcf6 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1,3 +1,2 @@",
+ "-object.someMethod(arg1, \"arg3\");",
+ "-object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg2\");",
+ "+object.someMethod(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "17eca3c171596d5fdaecd6141987f1c43509824b"
+ "shas": "51076f4ed7a3e7277b2d21eaecc04fe0ac703d33..52f38ade18e39d463dad479757df8039e8f9cfb9"
}
,{
"testCaseDescription": "javascript-method-call-delete-test",
@@ -1999,9 +2045,17 @@
"filePaths": [
"method-call.js"
],
- "sha1": "17eca3c171596d5fdaecd6141987f1c43509824b",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index 894dcf6..a82528c 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1,2 +1 @@",
+ "-object.someMethod(arg1, \"arg2\");",
+ " object.someMethod(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "01cea748071c345d2f01f378df0da61b5ccfa0f8"
+ "shas": "52f38ade18e39d463dad479757df8039e8f9cfb9..2b82d812ce523f1c1ec125ab8590a1cd7191bda9"
}
,{
"testCaseDescription": "javascript-method-call-delete-rest-test",
@@ -2109,7 +2163,14 @@
"filePaths": [
"method-call.js"
],
- "sha1": "01cea748071c345d2f01f378df0da61b5ccfa0f8",
+ "patch": [
+ "diff --git a/method-call.js b/method-call.js",
+ "index a82528c..e69de29 100644",
+ "--- a/method-call.js",
+ "+++ b/method-call.js",
+ "@@ -1 +0,0 @@",
+ "-object.someMethod(arg1, \"arg3\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "937d4af49d1685550ae5a457368e488ed62e26b0"
+ "shas": "2b82d812ce523f1c1ec125ab8590a1cd7191bda9..fc795a83fff7fcdcadac0ce15ce74b4c24bfcbd5"
}]
diff --git a/test/corpus/json/javascript/named-function.json b/test/corpus/json/javascript/named-function.json
index 1d30a1ad4..64cd0f92e 100644
--- a/test/corpus/json/javascript/named-function.json
+++ b/test/corpus/json/javascript/named-function.json
@@ -122,9 +122,16 @@
"filePaths": [
"named-function.js"
],
- "sha1": "2e98846e3a927bbf738f7d46ca9b6746840b89a7",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index e69de29..94b19f8 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -0,0 +1 @@",
+ "+function myFunction(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6db074f1c4e1a385daebe656bd946f3d013980ec"
+ "shas": "e3b9f963811fa510e777ed818a75408691e53555..26ef45fff727a1d92e4e7838001a2b035fc278e8"
}
,{
"testCaseDescription": "javascript-named-function-replacement-insert-test",
@@ -507,9 +514,18 @@
"filePaths": [
"named-function.js"
],
- "sha1": "6db074f1c4e1a385daebe656bd946f3d013980ec",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index 94b19f8..cb766a0 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1 +1,3 @@",
+ "+function anotherFunction() { return false; };",
+ "+function myFunction(arg1, arg2) { arg2; };",
+ " function myFunction(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "07c0a687a11f8f6dd8fa3cb6959e0ff03b5dff6b"
+ "shas": "26ef45fff727a1d92e4e7838001a2b035fc278e8..75a5271cdbee078430f84c42f7d1d117412b1113"
}
,{
"testCaseDescription": "javascript-named-function-delete-insert-test",
@@ -1062,9 +1078,19 @@
"filePaths": [
"named-function.js"
],
- "sha1": "07c0a687a11f8f6dd8fa3cb6959e0ff03b5dff6b",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index cb766a0..c9cff07 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function anotherFunction() { return false; };",
+ "+function myFunction(arg1, arg2) { arg2; };",
+ " function myFunction(arg1, arg2) { arg2; };",
+ " function myFunction(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "651f0fb5a86562dcdccbc952861a4ab7cf161e33"
+ "shas": "75a5271cdbee078430f84c42f7d1d117412b1113..09c3cd31554ad0960c5587fc0bea5d6c63208af1"
}
,{
"testCaseDescription": "javascript-named-function-replacement-test",
@@ -1617,9 +1643,19 @@
"filePaths": [
"named-function.js"
],
- "sha1": "651f0fb5a86562dcdccbc952861a4ab7cf161e33",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index c9cff07..cb766a0 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function myFunction(arg1, arg2) { arg2; };",
+ "+function anotherFunction() { return false; };",
+ " function myFunction(arg1, arg2) { arg2; };",
+ " function myFunction(arg1, arg2) { arg2; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "dbccaef0f14c268f2e76252528abdfffe8a41e39"
+ "shas": "09c3cd31554ad0960c5587fc0bea5d6c63208af1..780f471ede93bca59163186bb3b949234cbb34ad"
}
,{
"testCaseDescription": "javascript-named-function-delete-replacement-test",
@@ -2074,9 +2110,19 @@
"filePaths": [
"named-function.js"
],
- "sha1": "dbccaef0f14c268f2e76252528abdfffe8a41e39",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index cb766a0..148bcc7 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function anotherFunction() { return false; };",
+ "-function myFunction(arg1, arg2) { arg2; };",
+ " function myFunction(arg1, arg2) { arg2; };",
+ "+function anotherFunction() { return false; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7d82c10053ab1ccea70edfc980f2ef7b0cc74909"
+ "shas": "780f471ede93bca59163186bb3b949234cbb34ad..0d92f7f8cad59587e7bdcfdeee9fbdb9ccc97834"
}
,{
"testCaseDescription": "javascript-named-function-delete-test",
@@ -2359,9 +2405,17 @@
"filePaths": [
"named-function.js"
],
- "sha1": "7d82c10053ab1ccea70edfc980f2ef7b0cc74909",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index 148bcc7..80e11b0 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1,2 +1 @@",
+ "-function myFunction(arg1, arg2) { arg2; };",
+ " function anotherFunction() { return false; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "86d239d4baca5cf4a6f702da133385a1bc55a040"
+ "shas": "0d92f7f8cad59587e7bdcfdeee9fbdb9ccc97834..8ca0ac128c264aae6e22d2fd2d5d7afe05a25226"
}
,{
"testCaseDescription": "javascript-named-function-delete-rest-test",
@@ -2473,7 +2527,14 @@
"filePaths": [
"named-function.js"
],
- "sha1": "86d239d4baca5cf4a6f702da133385a1bc55a040",
+ "patch": [
+ "diff --git a/named-function.js b/named-function.js",
+ "index 80e11b0..e69de29 100644",
+ "--- a/named-function.js",
+ "+++ b/named-function.js",
+ "@@ -1 +0,0 @@",
+ "-function anotherFunction() { return false; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a816d0383b93d78bf467c1afad387fafe01c3111"
+ "shas": "8ca0ac128c264aae6e22d2fd2d5d7afe05a25226..6bb7b92e6660b4bea6500b17891e6215571694a1"
}]
diff --git a/test/corpus/json/javascript/nested-do-while-in-function.json b/test/corpus/json/javascript/nested-do-while-in-function.json
index 0bcbc9e05..43ce3ea92 100644
--- a/test/corpus/json/javascript/nested-do-while-in-function.json
+++ b/test/corpus/json/javascript/nested-do-while-in-function.json
@@ -163,9 +163,16 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "010fc7622a9bf32b411ac3d47a2d5570285347a6",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index e69de29..d205614 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -0,0 +1 @@",
+ "+function f(arg1, arg2) { do { something(arg1); } while (arg2); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e44e6e3c65155313ba0f5bb7cb77eb590908aee8"
+ "shas": "1eaceb51f0254fd4621ddd6e017876ef398d5d8e..dc15722d3808e5012e5bcf3a23499db0e1b7c995"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-replacement-insert-test",
@@ -726,9 +733,18 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "e44e6e3c65155313ba0f5bb7cb77eb590908aee8",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index d205614..5dfcca6 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1 +1,3 @@",
+ "+function f(arg1, arg2) { do { something(arg2); } while (arg1); }",
+ "+function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8f3f73498cd7a0b9c5a3fd48b2f41efa9480b8bc"
+ "shas": "dc15722d3808e5012e5bcf3a23499db0e1b7c995..7fa92c6f78c6d1456cdc90a1fa61b2388aeef6cd"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-insert-test",
@@ -1539,9 +1555,19 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "8f3f73498cd7a0b9c5a3fd48b2f41efa9480b8bc",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index 5dfcca6..49cff7e 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function f(arg1, arg2) { do { something(arg2); } while (arg1); }",
+ "+function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "65b78fe229c0a60b2b148dcbfe0569a20030d38e"
+ "shas": "7fa92c6f78c6d1456cdc90a1fa61b2388aeef6cd..fa3d4a9247fd7b7e73925554743a8744c9896695"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-replacement-test",
@@ -2352,9 +2378,19 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "65b78fe229c0a60b2b148dcbfe0569a20030d38e",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index 49cff7e..5dfcca6 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1,3 +1,3 @@",
+ "-function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ "+function f(arg1, arg2) { do { something(arg2); } while (arg1); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ba4b7a101b18416dac4f6fa24c4a40a5d0f3c2a9"
+ "shas": "fa3d4a9247fd7b7e73925554743a8744c9896695..7f3d2ac374c6ec185e40f87572406f9502997106"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-replacement-test",
@@ -3042,9 +3078,19 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "ba4b7a101b18416dac4f6fa24c4a40a5d0f3c2a9",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index 5dfcca6..babb1e6 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1,3 +1,2 @@",
+ "-function f(arg1, arg2) { do { something(arg2); } while (arg1); }",
+ "-function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ "+function f(arg1, arg2) { do { something(arg2); } while (arg1); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3c3e76d48ad79e538985e3819bd11c78e8d3d41c"
+ "shas": "7f3d2ac374c6ec185e40f87572406f9502997106..595f4e5c33c8379201bee89a298c78167dc96943"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-test",
@@ -3478,9 +3524,17 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "3c3e76d48ad79e538985e3819bd11c78e8d3d41c",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index babb1e6..2b15580 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1,2 +1 @@",
+ "-function f(arg1, arg2) { do { something(arg1); } while (arg2); }",
+ " function f(arg1, arg2) { do { something(arg2); } while (arg1); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fe186c294b9f080289e916a3b76e354b7c1143ae"
+ "shas": "595f4e5c33c8379201bee89a298c78167dc96943..81b84277f9f896d95d168abe4c1a79b6ef04f831"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-rest-test",
@@ -3647,7 +3701,14 @@
"filePaths": [
"nested-do-while-in-function.js"
],
- "sha1": "fe186c294b9f080289e916a3b76e354b7c1143ae",
+ "patch": [
+ "diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
+ "index 2b15580..e69de29 100644",
+ "--- a/nested-do-while-in-function.js",
+ "+++ b/nested-do-while-in-function.js",
+ "@@ -1 +0,0 @@",
+ "-function f(arg1, arg2) { do { something(arg2); } while (arg1); }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "81765d4b8506ea59264b4bdc0c5b8c2c78a0a1a2"
+ "shas": "81b84277f9f896d95d168abe4c1a79b6ef04f831..81a41e72cb6728374f1f2c700f5656622f0966ec"
}]
diff --git a/test/corpus/json/javascript/nested-functions.json b/test/corpus/json/javascript/nested-functions.json
index 345e805f1..2272cbdaa 100644
--- a/test/corpus/json/javascript/nested-functions.json
+++ b/test/corpus/json/javascript/nested-functions.json
@@ -232,9 +232,16 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "4993de9ab311936d640089fb8e5490f393d0e49d",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index e69de29..72531d8 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -0,0 +1 @@",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9753abca71c13d50fead82ef59ae4427fc8b837a"
+ "shas": "790f317cf635d64f5798d63a5b58483fd6bad99f..583329489c6f6b0bffd28c0ba69c284b7f1b811b"
}
,{
"testCaseDescription": "javascript-nested-functions-replacement-insert-test",
@@ -1071,9 +1078,18 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "9753abca71c13d50fead82ef59ae4427fc8b837a",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index 72531d8..c960aae 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1 +1,3 @@",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "94e1b740c83bde392a241dc82a439af9f2676955"
+ "shas": "583329489c6f6b0bffd28c0ba69c284b7f1b811b..5e0f442eda3b1d8f963cc7e248c5630420b5cff5"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-insert-test",
@@ -2298,9 +2314,19 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "94e1b740c83bde392a241dc82a439af9f2676955",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index c960aae..1b9b61a 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1,3 +1,3 @@",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d0fda84f6c55ed52a041aa88ecf37f2f403d8395"
+ "shas": "5e0f442eda3b1d8f963cc7e248c5630420b5cff5..4ce43f40272580f43a9fb8e2b7cdaf164023371b"
}
,{
"testCaseDescription": "javascript-nested-functions-replacement-test",
@@ -3525,9 +3551,19 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "d0fda84f6c55ed52a041aa88ecf37f2f403d8395",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index 1b9b61a..c960aae 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1,3 +1,3 @@",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3a5fa6c6690acc4d5adee977f537e5f98adf843b"
+ "shas": "4ce43f40272580f43a9fb8e2b7cdaf164023371b..66f83c285b323ea127caf0550c0dc30e999711af"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-replacement-test",
@@ -4560,9 +4596,19 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "3a5fa6c6690acc4d5adee977f537e5f98adf843b",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index c960aae..81522c7 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1,3 +1,2 @@",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ "+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f1787fc0b4b16d740902259de6a4563d983bf03a"
+ "shas": "66f83c285b323ea127caf0550c0dc30e999711af..f73fd1833e4219f46c9fbf2a4b40b819b299f142"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-test",
@@ -5203,9 +5249,17 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "f1787fc0b4b16d740902259de6a4563d983bf03a",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index 81522c7..3056480 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1,2 +1 @@",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }",
+ " function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a528a6232664e98a3ae81ddbdac951543658779e"
+ "shas": "f73fd1833e4219f46c9fbf2a4b40b819b299f142..eef7c0a54cfb951da941ad6f8697f41ee7eabc07"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-rest-test",
@@ -5441,7 +5495,14 @@
"filePaths": [
"nested-functions.js"
],
- "sha1": "a528a6232664e98a3ae81ddbdac951543658779e",
+ "patch": [
+ "diff --git a/nested-functions.js b/nested-functions.js",
+ "index 3056480..e69de29 100644",
+ "--- a/nested-functions.js",
+ "+++ b/nested-functions.js",
+ "@@ -1 +0,0 @@",
+ "-function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "010fc7622a9bf32b411ac3d47a2d5570285347a6"
+ "shas": "eef7c0a54cfb951da941ad6f8697f41ee7eabc07..1eaceb51f0254fd4621ddd6e017876ef398d5d8e"
}]
diff --git a/test/corpus/json/javascript/null.json b/test/corpus/json/javascript/null.json
index 5d6b8e045..c795064d7 100644
--- a/test/corpus/json/javascript/null.json
+++ b/test/corpus/json/javascript/null.json
@@ -74,9 +74,16 @@
"filePaths": [
"null.js"
],
- "sha1": "53e3f5fb29923247cf9f931d7662ac6ddb2fc6a0",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index e69de29..ff464d1 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -0,0 +1 @@",
+ "+null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3133a0d78daf8f5e0742ee5970a989055319993b"
+ "shas": "32100dbe7cbc819422359a14ab7495be3254310f..86f55a90cfe40fbdeeb68022238d81184f0932e0"
}
,{
"testCaseDescription": "javascript-null-replacement-insert-test",
@@ -281,9 +288,18 @@
"filePaths": [
"null.js"
],
- "sha1": "3133a0d78daf8f5e0742ee5970a989055319993b",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index ff464d1..2d3c3e0 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1 +1,3 @@",
+ "+return null;",
+ "+null;",
+ " null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "023f2b4852dafdca162b9e10b0e21ece5315b96e"
+ "shas": "86f55a90cfe40fbdeeb68022238d81184f0932e0..0289269250068ba7071ae26974fd3c8a7ed46ab0"
}
,{
"testCaseDescription": "javascript-null-delete-insert-test",
@@ -560,9 +576,19 @@
"filePaths": [
"null.js"
],
- "sha1": "023f2b4852dafdca162b9e10b0e21ece5315b96e",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index 2d3c3e0..3122897 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1,3 +1,3 @@",
+ "-return null;",
+ "+null;",
+ " null;",
+ " null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "be2838eea532c01abb873aaa0923b4f38393e330"
+ "shas": "0289269250068ba7071ae26974fd3c8a7ed46ab0..e48a4fe220f501abddbc4a16c44d570b990a3026"
}
,{
"testCaseDescription": "javascript-null-replacement-test",
@@ -839,9 +865,19 @@
"filePaths": [
"null.js"
],
- "sha1": "be2838eea532c01abb873aaa0923b4f38393e330",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index 3122897..2d3c3e0 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1,3 +1,3 @@",
+ "-null;",
+ "+return null;",
+ " null;",
+ " null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f0dd4e23e9a28c78c63e1363264aafc73d2051e7"
+ "shas": "e48a4fe220f501abddbc4a16c44d570b990a3026..4983cc8781e012c5884c8f077015d7a4ed689d67"
}
,{
"testCaseDescription": "javascript-null-delete-replacement-test",
@@ -1084,9 +1120,19 @@
"filePaths": [
"null.js"
],
- "sha1": "f0dd4e23e9a28c78c63e1363264aafc73d2051e7",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index 2d3c3e0..0eb99c8 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1,3 +1,2 @@",
+ "-return null;",
+ "-null;",
+ " null;",
+ "+return null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "03c10e1c0a4588730a26934c98353a8a42718bf8"
+ "shas": "4983cc8781e012c5884c8f077015d7a4ed689d67..cea8b90183ea7a84318980bb1b3934ee54b8a1f1"
}
,{
"testCaseDescription": "javascript-null-delete-test",
@@ -1253,9 +1299,17 @@
"filePaths": [
"null.js"
],
- "sha1": "03c10e1c0a4588730a26934c98353a8a42718bf8",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index 0eb99c8..76137ff 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1,2 +1 @@",
+ "-null;",
+ " return null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6d9f002c3e887ce0aff8172cb5adf0afd55fb3f7"
+ "shas": "cea8b90183ea7a84318980bb1b3934ee54b8a1f1..5dbd5eecb4a0dac8872d09eca47ac9717eca9abb"
}
,{
"testCaseDescription": "javascript-null-delete-rest-test",
@@ -1333,7 +1387,14 @@
"filePaths": [
"null.js"
],
- "sha1": "6d9f002c3e887ce0aff8172cb5adf0afd55fb3f7",
+ "patch": [
+ "diff --git a/null.js b/null.js",
+ "index 76137ff..e69de29 100644",
+ "--- a/null.js",
+ "+++ b/null.js",
+ "@@ -1 +0,0 @@",
+ "-return null;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f6fdfae045cfc2c5c89dec2ef98091dac6a57099"
+ "shas": "5dbd5eecb4a0dac8872d09eca47ac9717eca9abb..61695447b9d6c99d6fbee197c961837045e9237b"
}]
diff --git a/test/corpus/json/javascript/number.json b/test/corpus/json/javascript/number.json
index 1d39ea2d2..9f8c0ecdc 100644
--- a/test/corpus/json/javascript/number.json
+++ b/test/corpus/json/javascript/number.json
@@ -74,9 +74,16 @@
"filePaths": [
"number.js"
],
- "sha1": "9efe54b4d3f43994fbb659608be526dada4a01bc",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index e69de29..398050c 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -0,0 +1 @@",
+ "+101"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5a3568d7ab7595c185fba64a2e070ca382713967"
+ "shas": "f099c07f976a3deecc22768c671cc7ff3604a4e7..d2e50ce553db7a088ac51c4b4928cabab02e2ff9"
}
,{
"testCaseDescription": "javascript-number-replacement-insert-test",
@@ -281,9 +288,18 @@
"filePaths": [
"number.js"
],
- "sha1": "5a3568d7ab7595c185fba64a2e070ca382713967",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index 398050c..16da476 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1 +1,3 @@",
+ "+102",
+ "+101",
+ " 101"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d85e78cf0736c0854b31a0131e05121c54efcb50"
+ "shas": "d2e50ce553db7a088ac51c4b4928cabab02e2ff9..0ed8b90e49ac6b90b6e201c3f076f10089eb4498"
}
,{
"testCaseDescription": "javascript-number-delete-insert-test",
@@ -558,9 +574,19 @@
"filePaths": [
"number.js"
],
- "sha1": "d85e78cf0736c0854b31a0131e05121c54efcb50",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index 16da476..252b3e8 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1,3 +1,3 @@",
+ "-102",
+ "+101",
+ " 101",
+ " 101"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9fb2cc9edfd8993b90ea8f24a3e27ffc7cf366a1"
+ "shas": "0ed8b90e49ac6b90b6e201c3f076f10089eb4498..6ddf08fc0a1608bf1654e38b027fcfbb084afb1c"
}
,{
"testCaseDescription": "javascript-number-replacement-test",
@@ -835,9 +861,19 @@
"filePaths": [
"number.js"
],
- "sha1": "9fb2cc9edfd8993b90ea8f24a3e27ffc7cf366a1",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index 252b3e8..16da476 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1,3 +1,3 @@",
+ "-101",
+ "+102",
+ " 101",
+ " 101"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "437390581f555d263cbbbceeb12a1f8008198634"
+ "shas": "6ddf08fc0a1608bf1654e38b027fcfbb084afb1c..9083177390beeb4964e0c04c9f14d0b11747a08e"
}
,{
"testCaseDescription": "javascript-number-delete-replacement-test",
@@ -1080,9 +1116,19 @@
"filePaths": [
"number.js"
],
- "sha1": "437390581f555d263cbbbceeb12a1f8008198634",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index 16da476..bb77dfb 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1,3 +1,2 @@",
+ "-102",
+ "-101",
+ " 101",
+ "+102"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1c609e0fc767f755f1a8c7c7fc5dd449c09ebaee"
+ "shas": "9083177390beeb4964e0c04c9f14d0b11747a08e..91a9f6f544a6d00ee6e6578fb3d7934cda974e6f"
}
,{
"testCaseDescription": "javascript-number-delete-test",
@@ -1249,9 +1295,17 @@
"filePaths": [
"number.js"
],
- "sha1": "1c609e0fc767f755f1a8c7c7fc5dd449c09ebaee",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index bb77dfb..257e563 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1,2 +1 @@",
+ "-101",
+ " 102"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5a115eb52ca4c74f42633ffd23c832fb49694421"
+ "shas": "91a9f6f544a6d00ee6e6578fb3d7934cda974e6f..37cdd671605c31bf8013ad5d9e703390588df7fd"
}
,{
"testCaseDescription": "javascript-number-delete-rest-test",
@@ -1329,7 +1383,14 @@
"filePaths": [
"number.js"
],
- "sha1": "5a115eb52ca4c74f42633ffd23c832fb49694421",
+ "patch": [
+ "diff --git a/number.js b/number.js",
+ "index 257e563..e69de29 100644",
+ "--- a/number.js",
+ "+++ b/number.js",
+ "@@ -1 +0,0 @@",
+ "-102"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fc9b2f0c3bbc1743da1d9f7c05b00dce579743dc"
+ "shas": "37cdd671605c31bf8013ad5d9e703390588df7fd..3accaff544c4d4e390ec737b8c076a43e5d56563"
}]
diff --git a/test/corpus/json/javascript/object.json b/test/corpus/json/javascript/object.json
index 5bb5683d6..2e5a92167 100644
--- a/test/corpus/json/javascript/object.json
+++ b/test/corpus/json/javascript/object.json
@@ -99,9 +99,16 @@
"filePaths": [
"object.js"
],
- "sha1": "e56f285c01ffc201dab7b2d614c182bf1f49e269",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index e69de29..fe17bb2 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -0,0 +1 @@",
+ "+{ \"key1\": \"value1\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1fa374c4737c2ee6e4d6997ea427bb59c93f150d"
+ "shas": "925b73e9fde76236d0b037d687edcc925a5cef9a..ba5e502469d76330934d3f544642168b9a8be48e"
}
,{
"testCaseDescription": "javascript-object-replacement-insert-test",
@@ -452,9 +459,18 @@
"filePaths": [
"object.js"
],
- "sha1": "1fa374c4737c2ee6e4d6997ea427bb59c93f150d",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index fe17bb2..741c3dc 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1 +1,3 @@",
+ "+{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };",
+ "+{ \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0e49ef4a2de3ac58d75ebb1f7798bd89f150613c"
+ "shas": "ba5e502469d76330934d3f544642168b9a8be48e..83daa3599047a89477381c86dcc84c654773699f"
}
,{
"testCaseDescription": "javascript-object-delete-insert-test",
@@ -925,9 +941,19 @@
"filePaths": [
"object.js"
],
- "sha1": "0e49ef4a2de3ac58d75ebb1f7798bd89f150613c",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index 741c3dc..701239d 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1,3 +1,3 @@",
+ "-{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };",
+ "+{ \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "708aab840dfbd776e609935ab7b62a1c8de90340"
+ "shas": "83daa3599047a89477381c86dcc84c654773699f..8b139d9d6374dd725f251e360d9e1b85d4b74527"
}
,{
"testCaseDescription": "javascript-object-replacement-test",
@@ -1398,9 +1424,19 @@
"filePaths": [
"object.js"
],
- "sha1": "708aab840dfbd776e609935ab7b62a1c8de90340",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index 701239d..741c3dc 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1,3 +1,3 @@",
+ "-{ \"key1\": \"value1\" };",
+ "+{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };",
+ " { \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3c193fc885a4200d1cbd55f4cbac39fe5082d209"
+ "shas": "8b139d9d6374dd725f251e360d9e1b85d4b74527..f1d27fd392c566c9c5d26e2f239387a8079f149e"
}
,{
"testCaseDescription": "javascript-object-delete-replacement-test",
@@ -1860,9 +1896,19 @@
"filePaths": [
"object.js"
],
- "sha1": "3c193fc885a4200d1cbd55f4cbac39fe5082d209",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index 741c3dc..9e48273 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1,3 +1,2 @@",
+ "-{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };",
+ "-{ \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\" };",
+ "+{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "90e6412603611eb655811b075f58d8464e073f7f"
+ "shas": "f1d27fd392c566c9c5d26e2f239387a8079f149e..eefa16d6784883e1bcc084747522245c8875803d"
}
,{
"testCaseDescription": "javascript-object-delete-test",
@@ -2196,9 +2242,17 @@
"filePaths": [
"object.js"
],
- "sha1": "90e6412603611eb655811b075f58d8464e073f7f",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index 9e48273..12d063a 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1,2 +1 @@",
+ "-{ \"key1\": \"value1\" };",
+ " { \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e31566a724b61fc9bdcb74e98671f942d0404f67"
+ "shas": "eefa16d6784883e1bcc084747522245c8875803d..a9f043663130ffeeb0a948413011e9a72886d277"
}
,{
"testCaseDescription": "javascript-object-delete-rest-test",
@@ -2347,7 +2401,14 @@
"filePaths": [
"object.js"
],
- "sha1": "e31566a724b61fc9bdcb74e98671f942d0404f67",
+ "patch": [
+ "diff --git a/object.js b/object.js",
+ "index 12d063a..e69de29 100644",
+ "--- a/object.js",
+ "+++ b/object.js",
+ "@@ -1 +0,0 @@",
+ "-{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9e5406166a9e280d7ad6cc8bf570b450e90347a5"
+ "shas": "a9f043663130ffeeb0a948413011e9a72886d277..193d1078ef93cde9a03725d1f4b6a42b856754d3"
}]
diff --git a/test/corpus/json/javascript/objects-with-methods.json b/test/corpus/json/javascript/objects-with-methods.json
index d686d9c80..20e83a57c 100644
--- a/test/corpus/json/javascript/objects-with-methods.json
+++ b/test/corpus/json/javascript/objects-with-methods.json
@@ -138,9 +138,16 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "042a288ab3f8ef27e53f4354c48b71c03de8b2d2",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index e69de29..7421e18 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -0,0 +1 @@",
+ "+{ add(a, b) { return a + b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0b4b757145a89090f1d9fda258af68796f49599a"
+ "shas": "d85c24526768ef13d44a0e8cce5aefe270e43c4a..8eea4fae7706338a3f452fd4bd3055b37c97016a"
}
,{
"testCaseDescription": "javascript-objects-with-methods-replacement-insert-test",
@@ -601,9 +608,18 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "0b4b757145a89090f1d9fda258af68796f49599a",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 7421e18..59eb3a3 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1 +1,3 @@",
+ "+{ subtract(a, b) { return a - b; } };",
+ "+{ add(a, b) { return a + b; } };",
+ " { add(a, b) { return a + b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "262cd20347ec498fb9d0869124aeef7ff4c30f9b"
+ "shas": "8eea4fae7706338a3f452fd4bd3055b37c97016a..6eff566d865d623bc9da78e1d3effc0e71359b64"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-insert-test",
@@ -1262,9 +1278,19 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "262cd20347ec498fb9d0869124aeef7ff4c30f9b",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 59eb3a3..05689b1 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1,3 +1,3 @@",
+ "-{ subtract(a, b) { return a - b; } };",
+ "+{ add(a, b) { return a + b; } };",
+ " { add(a, b) { return a + b; } };",
+ " { add(a, b) { return a + b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "740ffd48f65ede4fe5602775c91fd73b31344c45"
+ "shas": "6eff566d865d623bc9da78e1d3effc0e71359b64..5e157004b3bbcf754390b5ea0b16a1293f239d41"
}
,{
"testCaseDescription": "javascript-objects-with-methods-replacement-test",
@@ -1923,9 +1949,19 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "740ffd48f65ede4fe5602775c91fd73b31344c45",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 05689b1..59eb3a3 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1,3 +1,3 @@",
+ "-{ add(a, b) { return a + b; } };",
+ "+{ subtract(a, b) { return a - b; } };",
+ " { add(a, b) { return a + b; } };",
+ " { add(a, b) { return a + b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "da7ba70730e97d6b0ddefb3dba28cfada5d6490d"
+ "shas": "5e157004b3bbcf754390b5ea0b16a1293f239d41..c31bcd1e44f97b7db87ff2b5a6cf0406e0d9e081"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-replacement-test",
@@ -2488,9 +2524,19 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "da7ba70730e97d6b0ddefb3dba28cfada5d6490d",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 59eb3a3..29d3998 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1,3 +1,2 @@",
+ "-{ subtract(a, b) { return a - b; } };",
+ "-{ add(a, b) { return a + b; } };",
+ " { add(a, b) { return a + b; } };",
+ "+{ subtract(a, b) { return a - b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1b6d7679d710850ec80ce067cce52a7953abc291"
+ "shas": "c31bcd1e44f97b7db87ff2b5a6cf0406e0d9e081..9224e4bb69acfd7cae9b2c42bef700ee0193975f"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-test",
@@ -2849,9 +2895,17 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "1b6d7679d710850ec80ce067cce52a7953abc291",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 29d3998..80ad7f0 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1,2 +1 @@",
+ "-{ add(a, b) { return a + b; } };",
+ " { subtract(a, b) { return a - b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ce0d8eb8162000c66e5bb9d49f36c0187e6b15c8"
+ "shas": "9224e4bb69acfd7cae9b2c42bef700ee0193975f..09865379a4ced5df31bdfc3432abeeb525fa8b53"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-rest-test",
@@ -2993,7 +3047,14 @@
"filePaths": [
"objects-with-methods.js"
],
- "sha1": "ce0d8eb8162000c66e5bb9d49f36c0187e6b15c8",
+ "patch": [
+ "diff --git a/objects-with-methods.js b/objects-with-methods.js",
+ "index 80ad7f0..e69de29 100644",
+ "--- a/objects-with-methods.js",
+ "+++ b/objects-with-methods.js",
+ "@@ -1 +0,0 @@",
+ "-{ subtract(a, b) { return a - b; } };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "954f6de645b21a3305ee051f7baf71d6c2d28f00"
+ "shas": "09865379a4ced5df31bdfc3432abeeb525fa8b53..b4b7955f8a8306e856b260875bdf3039b29612a8"
}]
diff --git a/test/corpus/json/javascript/regex.json b/test/corpus/json/javascript/regex.json
index f4d7e3356..3a165733e 100644
--- a/test/corpus/json/javascript/regex.json
+++ b/test/corpus/json/javascript/regex.json
@@ -74,9 +74,16 @@
"filePaths": [
"regex.js"
],
- "sha1": "432b804f2c2742a1c3e16957aea653610dc8daeb",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index e69de29..b381842 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -0,0 +1 @@",
+ "+/one/g;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b029d00cf5e92f122f25773af87fe26e092222af"
+ "shas": "38a4e343f701a84082bcd768e0389e8f827f85af..edc82ef64657537a6745a77405f29336c5f416bc"
}
,{
"testCaseDescription": "javascript-regex-replacement-insert-test",
@@ -281,9 +288,18 @@
"filePaths": [
"regex.js"
],
- "sha1": "b029d00cf5e92f122f25773af87fe26e092222af",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index b381842..6ed4b42 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1 +1,3 @@",
+ "+/on[^/]afe/gim;",
+ "+/one/g;",
+ " /one/g;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7cddea01b81341207a87d69aef60fb767aa69a57"
+ "shas": "edc82ef64657537a6745a77405f29336c5f416bc..88ff755ad131e5c05f0c6abcdae6b8e2f77f39a6"
}
,{
"testCaseDescription": "javascript-regex-delete-insert-test",
@@ -558,9 +574,19 @@
"filePaths": [
"regex.js"
],
- "sha1": "7cddea01b81341207a87d69aef60fb767aa69a57",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index 6ed4b42..abb87ec 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1,3 +1,3 @@",
+ "-/on[^/]afe/gim;",
+ "+/one/g;",
+ " /one/g;",
+ " /one/g;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6d168b838607471d418bb27f3233734ddad217e6"
+ "shas": "88ff755ad131e5c05f0c6abcdae6b8e2f77f39a6..10bb41b3b3a4df65d6616fc5d0e514ddad71ed9a"
}
,{
"testCaseDescription": "javascript-regex-replacement-test",
@@ -835,9 +861,19 @@
"filePaths": [
"regex.js"
],
- "sha1": "6d168b838607471d418bb27f3233734ddad217e6",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index abb87ec..6ed4b42 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1,3 +1,3 @@",
+ "-/one/g;",
+ "+/on[^/]afe/gim;",
+ " /one/g;",
+ " /one/g;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7fe5d0025e93e473b8007d6fedf8c0fb89df0c9b"
+ "shas": "10bb41b3b3a4df65d6616fc5d0e514ddad71ed9a..ffde850e3fe4fca0dfac3eb57899101e15b22d4c"
}
,{
"testCaseDescription": "javascript-regex-delete-replacement-test",
@@ -1080,9 +1116,19 @@
"filePaths": [
"regex.js"
],
- "sha1": "7fe5d0025e93e473b8007d6fedf8c0fb89df0c9b",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index 6ed4b42..9f57e91 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1,3 +1,2 @@",
+ "-/on[^/]afe/gim;",
+ "-/one/g;",
+ " /one/g;",
+ "+/on[^/]afe/gim;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "29c9082953f521e4220bf7b788eaac1f3a3c5b61"
+ "shas": "ffde850e3fe4fca0dfac3eb57899101e15b22d4c..c1a636c92ae8fafe7a7bb251771d96306e59297c"
}
,{
"testCaseDescription": "javascript-regex-delete-test",
@@ -1249,9 +1295,17 @@
"filePaths": [
"regex.js"
],
- "sha1": "29c9082953f521e4220bf7b788eaac1f3a3c5b61",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index 9f57e91..9b04194 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1,2 +1 @@",
+ "-/one/g;",
+ " /on[^/]afe/gim;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4b0b35b2d4ce8085bc1940949b33d34768026a14"
+ "shas": "c1a636c92ae8fafe7a7bb251771d96306e59297c..598fffd310ec3abebf3f54dbdd383ef2c1a10689"
}
,{
"testCaseDescription": "javascript-regex-delete-rest-test",
@@ -1329,7 +1383,14 @@
"filePaths": [
"regex.js"
],
- "sha1": "4b0b35b2d4ce8085bc1940949b33d34768026a14",
+ "patch": [
+ "diff --git a/regex.js b/regex.js",
+ "index 9b04194..e69de29 100644",
+ "--- a/regex.js",
+ "+++ b/regex.js",
+ "@@ -1 +0,0 @@",
+ "-/on[^/]afe/gim;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f6609017b201ccacdd96341f8be7440ed0396418"
+ "shas": "598fffd310ec3abebf3f54dbdd383ef2c1a10689..1414e435bed741828bc662b2617b65f006198115"
}]
diff --git a/test/corpus/json/javascript/relational-operator.json b/test/corpus/json/javascript/relational-operator.json
index 58918566e..2e95a92f4 100644
--- a/test/corpus/json/javascript/relational-operator.json
+++ b/test/corpus/json/javascript/relational-operator.json
@@ -90,9 +90,16 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "a919283c34de839a761ede23220cbfb06d95fc5e",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index e69de29..4021910 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -0,0 +1 @@",
+ "+x < y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6f0b4481386af74840df4ebfdb08231f5c84e131"
+ "shas": "ba72732ac272c8ae8487ba0af9045dea54eb02d9..3e474168119e157dd78cc58193422367455f7d4b"
}
,{
"testCaseDescription": "javascript-relational-operator-replacement-insert-test",
@@ -361,9 +368,18 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "6f0b4481386af74840df4ebfdb08231f5c84e131",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index 4021910..dbef050 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1 +1,3 @@",
+ "+x <= y;",
+ "+x < y;",
+ " x < y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "dd659ba5e7a414307340a5a4570a21bbcc384d8a"
+ "shas": "3e474168119e157dd78cc58193422367455f7d4b..80299a9d43818b539001b6d79fc5b2a4060e7c51"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-insert-test",
@@ -732,9 +748,19 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "dd659ba5e7a414307340a5a4570a21bbcc384d8a",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index dbef050..a9ff7f6 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-x <= y;",
+ "+x < y;",
+ " x < y;",
+ " x < y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8d831be60c4871818beb03d2ebb6bceb3d95eac8"
+ "shas": "80299a9d43818b539001b6d79fc5b2a4060e7c51..d908f67a8ee9d6610371bb8343c67b172f915b23"
}
,{
"testCaseDescription": "javascript-relational-operator-replacement-test",
@@ -1103,9 +1129,19 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "8d831be60c4871818beb03d2ebb6bceb3d95eac8",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index a9ff7f6..dbef050 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-x < y;",
+ "+x <= y;",
+ " x < y;",
+ " x < y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "59ebb3564bdf427b5b5ddb5df4541bf09dc5d5b4"
+ "shas": "d908f67a8ee9d6610371bb8343c67b172f915b23..b553dcd439cdfb5d1b6846389ed69bbff93ada3d"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-replacement-test",
@@ -1424,9 +1460,19 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "59ebb3564bdf427b5b5ddb5df4541bf09dc5d5b4",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index dbef050..1ee42eb 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-x <= y;",
+ "-x < y;",
+ " x < y;",
+ "+x <= y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b04246c2e0dd010ca1c49e6f440f60b71f136b4a"
+ "shas": "b553dcd439cdfb5d1b6846389ed69bbff93ada3d..b0570894175ea4fdd408d62919b08db9d82eac0d"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-test",
@@ -1641,9 +1687,17 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "b04246c2e0dd010ca1c49e6f440f60b71f136b4a",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index 1ee42eb..3be8450 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1,2 +1 @@",
+ "-x < y;",
+ " x <= y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8011c74e25c32e350a110f23ea5d183f48b6adbe"
+ "shas": "b0570894175ea4fdd408d62919b08db9d82eac0d..f90601d7c97c8e74625f9724a011cb40ee870ec2"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-rest-test",
@@ -1737,7 +1791,14 @@
"filePaths": [
"relational-operator.js"
],
- "sha1": "8011c74e25c32e350a110f23ea5d183f48b6adbe",
+ "patch": [
+ "diff --git a/relational-operator.js b/relational-operator.js",
+ "index 3be8450..e69de29 100644",
+ "--- a/relational-operator.js",
+ "+++ b/relational-operator.js",
+ "@@ -1 +0,0 @@",
+ "-x <= y;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f6f1a76087498759b09a64e05a2d7c1867a77ff3"
+ "shas": "f90601d7c97c8e74625f9724a011cb40ee870ec2..6ca5e77d4063360bcd0a90d891c3e81e09835b84"
}]
diff --git a/test/corpus/json/javascript/return-statement.json b/test/corpus/json/javascript/return-statement.json
index 2c54ccdf8..b16c17890 100644
--- a/test/corpus/json/javascript/return-statement.json
+++ b/test/corpus/json/javascript/return-statement.json
@@ -74,9 +74,16 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "c26d48032e032fd0fc1650e48cee5545f6337902",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index e69de29..6315029 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -0,0 +1 @@",
+ "+return 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3eb406b4b30859658f540257356b8372bce7eba7"
+ "shas": "9fdae081cef5395f539eef79836a911574344379..a6519eaebdf537fde59ebe64592c4809e1687d84"
}
,{
"testCaseDescription": "javascript-return-statement-replacement-insert-test",
@@ -273,9 +280,18 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "3eb406b4b30859658f540257356b8372bce7eba7",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index 6315029..22dde95 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1 +1,3 @@",
+ "+return;",
+ "+return 5;",
+ " return 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "49f5fa1ef87d8690b07c563ce17f2f5cdedc4ef0"
+ "shas": "a6519eaebdf537fde59ebe64592c4809e1687d84..70590b307748041027a3074e4e8568ae9bbea413"
}
,{
"testCaseDescription": "javascript-return-statement-delete-insert-test",
@@ -543,9 +559,19 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "49f5fa1ef87d8690b07c563ce17f2f5cdedc4ef0",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index 22dde95..522349c 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-return;",
+ "+return 5;",
+ " return 5;",
+ " return 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9ca1e345d582da4d6e8e64c0d1b5025dc601d0c4"
+ "shas": "70590b307748041027a3074e4e8568ae9bbea413..21febb1d7f52af48f7d71d6b063371ae1e7ee66c"
}
,{
"testCaseDescription": "javascript-return-statement-replacement-test",
@@ -813,9 +839,19 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "9ca1e345d582da4d6e8e64c0d1b5025dc601d0c4",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index 522349c..22dde95 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-return 5;",
+ "+return;",
+ " return 5;",
+ " return 5;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5f2948710ef315b8bf0ad73d1886d55fa4dc493c"
+ "shas": "21febb1d7f52af48f7d71d6b063371ae1e7ee66c..8b962deb58f1b589be0cdede381164f4c8b02fac"
}
,{
"testCaseDescription": "javascript-return-statement-delete-replacement-test",
@@ -1042,9 +1078,19 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "5f2948710ef315b8bf0ad73d1886d55fa4dc493c",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index 22dde95..4d44d6a 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-return;",
+ "-return 5;",
+ " return 5;",
+ "+return;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6669db5ce9cb1d0414a4bbe0ff6811aa62147fc3"
+ "shas": "8b962deb58f1b589be0cdede381164f4c8b02fac..90bc3b8759268da9a86a1e27674f462916546ca8"
}
,{
"testCaseDescription": "javascript-return-statement-delete-test",
@@ -1195,9 +1241,17 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "6669db5ce9cb1d0414a4bbe0ff6811aa62147fc3",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index 4d44d6a..f312410 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1,2 +1 @@",
+ "-return 5;",
+ " return;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "86b03316284ecc5e3f92031727aded8ab596a705"
+ "shas": "90bc3b8759268da9a86a1e27674f462916546ca8..e60ebebf754719b6c7025fd60e409ca738c7dec6"
}
,{
"testCaseDescription": "javascript-return-statement-delete-rest-test",
@@ -1267,7 +1321,14 @@
"filePaths": [
"return-statement.js"
],
- "sha1": "86b03316284ecc5e3f92031727aded8ab596a705",
+ "patch": [
+ "diff --git a/return-statement.js b/return-statement.js",
+ "index f312410..e69de29 100644",
+ "--- a/return-statement.js",
+ "+++ b/return-statement.js",
+ "@@ -1 +0,0 @@",
+ "-return;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7ed50d1404aa1f2b612ab1e1ec31c028d7670964"
+ "shas": "e60ebebf754719b6c7025fd60e409ca738c7dec6..3a0405bd7047ac7693031b2b8fc3060c111cc827"
}]
diff --git a/test/corpus/json/javascript/string.json b/test/corpus/json/javascript/string.json
index f205995e4..bec607d5c 100644
--- a/test/corpus/json/javascript/string.json
+++ b/test/corpus/json/javascript/string.json
@@ -74,9 +74,16 @@
"filePaths": [
"string.js"
],
- "sha1": "954f6de645b21a3305ee051f7baf71d6c2d28f00",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index e69de29..ea5bd42 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -0,0 +1 @@",
+ "+'A string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2ec6001dd34498939531427aa22e78fa0afb91dd"
+ "shas": "b4b7955f8a8306e856b260875bdf3039b29612a8..1ae82ffe90486e07c465d7ef6d1c187adaea9f57"
}
,{
"testCaseDescription": "javascript-string-replacement-insert-test",
@@ -281,9 +288,18 @@
"filePaths": [
"string.js"
],
- "sha1": "2ec6001dd34498939531427aa22e78fa0afb91dd",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index ea5bd42..5cef047 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1 +1,3 @@",
+ "+'A different string with \"double\" quotes';",
+ "+'A string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9eb3deae19f408ceab51f467788ed5eb5af1d22f"
+ "shas": "1ae82ffe90486e07c465d7ef6d1c187adaea9f57..1aaf4eb23170cf9fbb6ba792fcad78a69c7cc718"
}
,{
"testCaseDescription": "javascript-string-delete-insert-test",
@@ -558,9 +574,19 @@
"filePaths": [
"string.js"
],
- "sha1": "9eb3deae19f408ceab51f467788ed5eb5af1d22f",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index 5cef047..7af39a5 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1,3 +1,3 @@",
+ "-'A different string with \"double\" quotes';",
+ "+'A string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "095b621ae55a5f630f91de653a9bbb4258c2f917"
+ "shas": "1aaf4eb23170cf9fbb6ba792fcad78a69c7cc718..f2605de89ead3607784d2290a6c252eb77d19d48"
}
,{
"testCaseDescription": "javascript-string-replacement-test",
@@ -835,9 +861,19 @@
"filePaths": [
"string.js"
],
- "sha1": "095b621ae55a5f630f91de653a9bbb4258c2f917",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index 7af39a5..5cef047 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1,3 +1,3 @@",
+ "-'A string with \"double\" quotes';",
+ "+'A different string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a80f3999ca08acd0f7772f3a0302dfdf26fee813"
+ "shas": "f2605de89ead3607784d2290a6c252eb77d19d48..0d6c84d2451d8516113faa5e7ba3f7c16d677d77"
}
,{
"testCaseDescription": "javascript-string-delete-replacement-test",
@@ -1080,9 +1116,19 @@
"filePaths": [
"string.js"
],
- "sha1": "a80f3999ca08acd0f7772f3a0302dfdf26fee813",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index 5cef047..8dd4514 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1,3 +1,2 @@",
+ "-'A different string with \"double\" quotes';",
+ "-'A string with \"double\" quotes';",
+ " 'A string with \"double\" quotes';",
+ "+'A different string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2962ba5a70c69ae5779d647732932de206fadd47"
+ "shas": "0d6c84d2451d8516113faa5e7ba3f7c16d677d77..487e572b835a23965a17ef170fae6f8923c80207"
}
,{
"testCaseDescription": "javascript-string-delete-test",
@@ -1249,9 +1295,17 @@
"filePaths": [
"string.js"
],
- "sha1": "2962ba5a70c69ae5779d647732932de206fadd47",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index 8dd4514..95fbde5 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1,2 +1 @@",
+ "-'A string with \"double\" quotes';",
+ " 'A different string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0415b106f557c84b6ab433005990488f61eca210"
+ "shas": "487e572b835a23965a17ef170fae6f8923c80207..898024c3d9b85c0c58a8615a308c6064aebaa0b0"
}
,{
"testCaseDescription": "javascript-string-delete-rest-test",
@@ -1329,7 +1383,14 @@
"filePaths": [
"string.js"
],
- "sha1": "0415b106f557c84b6ab433005990488f61eca210",
+ "patch": [
+ "diff --git a/string.js b/string.js",
+ "index 95fbde5..e69de29 100644",
+ "--- a/string.js",
+ "+++ b/string.js",
+ "@@ -1 +0,0 @@",
+ "-'A different string with \"double\" quotes';"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9efe54b4d3f43994fbb659608be526dada4a01bc"
+ "shas": "898024c3d9b85c0c58a8615a308c6064aebaa0b0..f099c07f976a3deecc22768c671cc7ff3604a4e7"
}]
diff --git a/test/corpus/json/javascript/subscript-access-assignment.json b/test/corpus/json/javascript/subscript-access-assignment.json
index c895bd532..5cd66cabb 100644
--- a/test/corpus/json/javascript/subscript-access-assignment.json
+++ b/test/corpus/json/javascript/subscript-access-assignment.json
@@ -106,9 +106,16 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "2984e6c47cb68c823069ad8467e3f43d0b833207",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index e69de29..6b6d48d 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -0,0 +1 @@",
+ "+y[\"x\"] = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "87567d99040fff0d1dcc60488971e8fff1f0b47d"
+ "shas": "6a942b8c8b6674795040d75810b847dd6dbf37e4..3ac2b12795f6310d1062f1d3357234b9039ef595"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test",
@@ -441,9 +448,18 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "87567d99040fff0d1dcc60488971e8fff1f0b47d",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index 6b6d48d..17d3ff4 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1 +1,3 @@",
+ "+y[\"x\"] = 1;",
+ "+y[\"x\"] = 0;",
+ " y[\"x\"] = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "163e6ed946d767356284e4190f994827b5a57462"
+ "shas": "3ac2b12795f6310d1062f1d3357234b9039ef595..e487cba908f3e34fbc0dae932b63d7dfdcf84485"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test",
@@ -910,9 +926,19 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "163e6ed946d767356284e4190f994827b5a57462",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index 17d3ff4..d856ac0 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-y[\"x\"] = 1;",
+ "+y[\"x\"] = 0;",
+ " y[\"x\"] = 0;",
+ " y[\"x\"] = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "717e27f03f82e4f24638c215365b4fa9c17c6476"
+ "shas": "e487cba908f3e34fbc0dae932b63d7dfdcf84485..1abda3dbd17bb194be11ea0d1e52d66d213a76c6"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-replacement-test",
@@ -1379,9 +1405,19 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "717e27f03f82e4f24638c215365b4fa9c17c6476",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index d856ac0..17d3ff4 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1,3 +1,3 @@",
+ "-y[\"x\"] = 0;",
+ "+y[\"x\"] = 1;",
+ " y[\"x\"] = 0;",
+ " y[\"x\"] = 0;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3614bd706e9fc192fc4df11fb91238b4081d8222"
+ "shas": "1abda3dbd17bb194be11ea0d1e52d66d213a76c6..049c51e69ba53fe3a11b4936f2454d4c4f648c05"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test",
@@ -1784,9 +1820,19 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "3614bd706e9fc192fc4df11fb91238b4081d8222",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index 17d3ff4..cdcb426 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1,3 +1,2 @@",
+ "-y[\"x\"] = 1;",
+ "-y[\"x\"] = 0;",
+ " y[\"x\"] = 0;",
+ "+y[\"x\"] = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4d98d85bacf52f11c4b592424e43545a04760b00"
+ "shas": "049c51e69ba53fe3a11b4936f2454d4c4f648c05..2a80663675514f8ea8a9ee9da926bc5c4d062dd7"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-test",
@@ -2049,9 +2095,17 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "4d98d85bacf52f11c4b592424e43545a04760b00",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index cdcb426..0407c3a 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1,2 +1 @@",
+ "-y[\"x\"] = 0;",
+ " y[\"x\"] = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fbafce95855b35a27c676970072fd1f1d179daf8"
+ "shas": "2a80663675514f8ea8a9ee9da926bc5c4d062dd7..ad6c13f941554247a24c825e4d6a517fbcf55a69"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test",
@@ -2161,7 +2215,14 @@
"filePaths": [
"subscript-access-assignment.js"
],
- "sha1": "fbafce95855b35a27c676970072fd1f1d179daf8",
+ "patch": [
+ "diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
+ "index 0407c3a..e69de29 100644",
+ "--- a/subscript-access-assignment.js",
+ "+++ b/subscript-access-assignment.js",
+ "@@ -1 +0,0 @@",
+ "-y[\"x\"] = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a166f0bf388151fe02e1579dd52048ffbac7ba1e"
+ "shas": "ad6c13f941554247a24c825e4d6a517fbcf55a69..ac9dba90a6e274a0ed1a230da35e51fd47c0eef4"
}]
diff --git a/test/corpus/json/javascript/subscript-access-string.json b/test/corpus/json/javascript/subscript-access-string.json
index 3132fa664..dd8a1a2b1 100644
--- a/test/corpus/json/javascript/subscript-access-string.json
+++ b/test/corpus/json/javascript/subscript-access-string.json
@@ -90,9 +90,16 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "e11abbd7db106d99d917a5ad4dc0e0bb84f015c4",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index e69de29..4293717 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -0,0 +1 @@",
+ "+x[\"some-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b936bc34c7655415db218b0ba69cd07a8619cc1f"
+ "shas": "b120fb35e9c89d5480c33ff8e9e5d6e5e3632044..dd9d1fbb38c80adc7d93543e65d007cee202ccda"
}
,{
"testCaseDescription": "javascript-subscript-access-string-replacement-insert-test",
@@ -361,9 +368,18 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "b936bc34c7655415db218b0ba69cd07a8619cc1f",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index 4293717..4293009 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1 +1,3 @@",
+ "+x[\"some-other-string\"];",
+ "+x[\"some-string\"];",
+ " x[\"some-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e66ca7baf9a62a4b20e1ec5e26cb28ebeb4e5b8f"
+ "shas": "dd9d1fbb38c80adc7d93543e65d007cee202ccda..5fa07084afb4fe828fd53c393c48c3231ecbe900"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-insert-test",
@@ -734,9 +750,19 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "e66ca7baf9a62a4b20e1ec5e26cb28ebeb4e5b8f",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index 4293009..c53d07b 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1,3 +1,3 @@",
+ "-x[\"some-other-string\"];",
+ "+x[\"some-string\"];",
+ " x[\"some-string\"];",
+ " x[\"some-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "502f190aa7888975d76c60586066547bc3b9a491"
+ "shas": "5fa07084afb4fe828fd53c393c48c3231ecbe900..4489ef48c1815a018870abb9af375cf9e6fcd5d9"
}
,{
"testCaseDescription": "javascript-subscript-access-string-replacement-test",
@@ -1107,9 +1133,19 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "502f190aa7888975d76c60586066547bc3b9a491",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index c53d07b..4293009 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1,3 +1,3 @@",
+ "-x[\"some-string\"];",
+ "+x[\"some-other-string\"];",
+ " x[\"some-string\"];",
+ " x[\"some-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5cc2450347198f0dac26176374c5b7decae00bb0"
+ "shas": "4489ef48c1815a018870abb9af375cf9e6fcd5d9..f0af83c1698f1b4d000ab66e4432d87b0620d75c"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-replacement-test",
@@ -1432,9 +1468,19 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "5cc2450347198f0dac26176374c5b7decae00bb0",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index 4293009..89c1bc2 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1,3 +1,2 @@",
+ "-x[\"some-other-string\"];",
+ "-x[\"some-string\"];",
+ " x[\"some-string\"];",
+ "+x[\"some-other-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "af1f11c4a8c49614fd214e5ec80304862f8fb730"
+ "shas": "f0af83c1698f1b4d000ab66e4432d87b0620d75c..e35c768f935b688b4f01e54dd0b370e63c17d745"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-test",
@@ -1649,9 +1695,17 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "af1f11c4a8c49614fd214e5ec80304862f8fb730",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index 89c1bc2..758f8e7 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1,2 +1 @@",
+ "-x[\"some-string\"];",
+ " x[\"some-other-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c702dfa0c6e74182a4cf7240217d07057e1c31b7"
+ "shas": "e35c768f935b688b4f01e54dd0b370e63c17d745..f09c45712b4b483d42fa9eea14005cfffb916cb9"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-rest-test",
@@ -1745,7 +1799,14 @@
"filePaths": [
"subscript-access-string.js"
],
- "sha1": "c702dfa0c6e74182a4cf7240217d07057e1c31b7",
+ "patch": [
+ "diff --git a/subscript-access-string.js b/subscript-access-string.js",
+ "index 758f8e7..e69de29 100644",
+ "--- a/subscript-access-string.js",
+ "+++ b/subscript-access-string.js",
+ "@@ -1 +0,0 @@",
+ "-x[\"some-other-string\"];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4986fadfc0f8ecf1f3b66745c95cf2b6ab739abb"
+ "shas": "f09c45712b4b483d42fa9eea14005cfffb916cb9..6a24d1bc284fee3110e5699439106922f5381fd5"
}]
diff --git a/test/corpus/json/javascript/subscript-access-variable.json b/test/corpus/json/javascript/subscript-access-variable.json
index af046b643..9797ac933 100644
--- a/test/corpus/json/javascript/subscript-access-variable.json
+++ b/test/corpus/json/javascript/subscript-access-variable.json
@@ -90,9 +90,16 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "287b6fa60bf503572cbcddbf84c46e81f3f4008c",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index e69de29..9a7b3d3 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -0,0 +1 @@",
+ "+x[someVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9385b68e7f821b3950df48030cd08e458ae16a00"
+ "shas": "75ba258ab370ff0efecb47f5f6a2f6a9968e9b8d..23c97f1701f504da098e41630d463fde923ef329"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test",
@@ -361,9 +368,18 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "9385b68e7f821b3950df48030cd08e458ae16a00",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index 9a7b3d3..000d190 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1 +1,3 @@",
+ "+x[someOtherVariable];",
+ "+x[someVariable];",
+ " x[someVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "94d8350ed59b0becec0aeebd320682a9d1c0f949"
+ "shas": "23c97f1701f504da098e41630d463fde923ef329..d31176af5821d8c2be72bfb9313f424b2b21f883"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-insert-test",
@@ -734,9 +750,19 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "94d8350ed59b0becec0aeebd320682a9d1c0f949",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index 000d190..01f61ef 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1,3 +1,3 @@",
+ "-x[someOtherVariable];",
+ "+x[someVariable];",
+ " x[someVariable];",
+ " x[someVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "099a661c8bfb9208a3509f11b746c4aa61c91752"
+ "shas": "d31176af5821d8c2be72bfb9313f424b2b21f883..35cfecb96f5660cb9ae603f56d49853d1ab357c0"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-replacement-test",
@@ -1107,9 +1133,19 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "099a661c8bfb9208a3509f11b746c4aa61c91752",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index 01f61ef..000d190 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1,3 +1,3 @@",
+ "-x[someVariable];",
+ "+x[someOtherVariable];",
+ " x[someVariable];",
+ " x[someVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "82c928c141983e5c53bf1cfa3e14507383a474fa"
+ "shas": "35cfecb96f5660cb9ae603f56d49853d1ab357c0..a016d5179e851e36e838d44502bc212e05b27fd0"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test",
@@ -1432,9 +1468,19 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "82c928c141983e5c53bf1cfa3e14507383a474fa",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index 000d190..2aaae7e 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1,3 +1,2 @@",
+ "-x[someOtherVariable];",
+ "-x[someVariable];",
+ " x[someVariable];",
+ "+x[someOtherVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4e55777977fc0908da49083edf1927e54103dda8"
+ "shas": "a016d5179e851e36e838d44502bc212e05b27fd0..6cb518ca4bddfb965e79b029574ca2f66d3ba324"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-test",
@@ -1649,9 +1695,17 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "4e55777977fc0908da49083edf1927e54103dda8",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index 2aaae7e..baa3661 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1,2 +1 @@",
+ "-x[someVariable];",
+ " x[someOtherVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fdf8b9a33dcbbdd3629985a84658381f21625eef"
+ "shas": "6cb518ca4bddfb965e79b029574ca2f66d3ba324..a94c11e468e53c7366ae98264e0e2655f9a239e0"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-rest-test",
@@ -1745,7 +1799,14 @@
"filePaths": [
"subscript-access-variable.js"
],
- "sha1": "fdf8b9a33dcbbdd3629985a84658381f21625eef",
+ "patch": [
+ "diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
+ "index baa3661..e69de29 100644",
+ "--- a/subscript-access-variable.js",
+ "+++ b/subscript-access-variable.js",
+ "@@ -1 +0,0 @@",
+ "-x[someOtherVariable];"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e11abbd7db106d99d917a5ad4dc0e0bb84f015c4"
+ "shas": "a94c11e468e53c7366ae98264e0e2655f9a239e0..b120fb35e9c89d5480c33ff8e9e5d6e5e3632044"
}]
diff --git a/test/corpus/json/javascript/switch-statement.json b/test/corpus/json/javascript/switch-statement.json
index 6398f6778..f8b509644 100644
--- a/test/corpus/json/javascript/switch-statement.json
+++ b/test/corpus/json/javascript/switch-statement.json
@@ -170,9 +170,16 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "4a90972f24ee5161810f26170784ea8342d7bab5",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index e69de29..5481c49 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -0,0 +1 @@",
+ "+switch (1) { case 1: 1; case 2: 1; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c300a3a9ddd9b4c8aadd3b8592368b537b60151b"
+ "shas": "954df1246c20f230e519c9fb74e256a93cd3e92a..102a1103adca089b9176c54ed7fa1cf8acb4c77f"
}
,{
"testCaseDescription": "javascript-switch-statement-replacement-insert-test",
@@ -761,9 +768,18 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "c300a3a9ddd9b4c8aadd3b8592368b537b60151b",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index 5481c49..ffd4a32 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1 +1,3 @@",
+ "+switch (2) { case 1: 1; case 2: 2; case 3: 3; };",
+ "+switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0fccf1f099cc888ac169693d193ace6b77514385"
+ "shas": "102a1103adca089b9176c54ed7fa1cf8acb4c77f..6f1d2c228e9cbc259fdfd2026ce0e3960c3bf976"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-insert-test",
@@ -1616,9 +1632,19 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "0fccf1f099cc888ac169693d193ace6b77514385",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index ffd4a32..302fb8b 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-switch (2) { case 1: 1; case 2: 2; case 3: 3; };",
+ "+switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "93be58225d5244cc66163a0ece00d93958322cda"
+ "shas": "6f1d2c228e9cbc259fdfd2026ce0e3960c3bf976..0b3287553c97194548459416885e547386f2197d"
}
,{
"testCaseDescription": "javascript-switch-statement-replacement-test",
@@ -2471,9 +2497,19 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "93be58225d5244cc66163a0ece00d93958322cda",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index 302fb8b..ffd4a32 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ "+switch (2) { case 1: 1; case 2: 2; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b0e772e7aaee7cff1cf847d8a8c51c16fe84b0ba"
+ "shas": "0b3287553c97194548459416885e547386f2197d..7a73e15cd2ea90a073cc3690e23fe6c0aa6849b2"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-replacement-test",
@@ -3196,9 +3232,19 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "b0e772e7aaee7cff1cf847d8a8c51c16fe84b0ba",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index ffd4a32..9b60579 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-switch (2) { case 1: 1; case 2: 2; case 3: 3; };",
+ "-switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ "+switch (2) { case 1: 1; case 2: 2; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "79d9ea2814ccbda54519504632b26f68ecd3c6b0"
+ "shas": "7a73e15cd2ea90a073cc3690e23fe6c0aa6849b2..d076963c4618fdd6dc59aba52ee0d4d9f0273bbd"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-test",
@@ -3653,9 +3699,17 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "79d9ea2814ccbda54519504632b26f68ecd3c6b0",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index 9b60579..374091f 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1,2 +1 @@",
+ "-switch (1) { case 1: 1; case 2: 1; case 3: 3; };",
+ " switch (2) { case 1: 1; case 2: 2; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "616bf89030ecc89bb6fb3f69a9ae0740bb5aad29"
+ "shas": "d076963c4618fdd6dc59aba52ee0d4d9f0273bbd..3b8a2a002e5cf23fa242fab45be41d23d0269feb"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-rest-test",
@@ -3829,7 +3883,14 @@
"filePaths": [
"switch-statement.js"
],
- "sha1": "616bf89030ecc89bb6fb3f69a9ae0740bb5aad29",
+ "patch": [
+ "diff --git a/switch-statement.js b/switch-statement.js",
+ "index 374091f..e69de29 100644",
+ "--- a/switch-statement.js",
+ "+++ b/switch-statement.js",
+ "@@ -1 +0,0 @@",
+ "-switch (2) { case 1: 1; case 2: 2; case 3: 3; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f3b243e075c09050d6b896d8240e38144679a57d"
+ "shas": "3b8a2a002e5cf23fa242fab45be41d23d0269feb..5feeb9240c4cfaac7dec387bafe580d79ff959c8"
}]
diff --git a/test/corpus/json/javascript/template-string.json b/test/corpus/json/javascript/template-string.json
index 88ce7bb5f..9d55e2e5b 100644
--- a/test/corpus/json/javascript/template-string.json
+++ b/test/corpus/json/javascript/template-string.json
@@ -74,9 +74,16 @@
"filePaths": [
"template-string.js"
],
- "sha1": "57942e93fabda394bc01cee76c0313089454e309",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index e69de29..01f859b 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -0,0 +1 @@",
+ "+`one line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e614a872cd77eefb0bd2dfea4bb7da0794c152fb"
+ "shas": "c32361c31b256ea32638cead8a9639d9d3bb55d4..eadba66cb97d885739f3686453ed93fc62b92191"
}
,{
"testCaseDescription": "javascript-template-string-replacement-insert-test",
@@ -281,9 +288,18 @@
"filePaths": [
"template-string.js"
],
- "sha1": "e614a872cd77eefb0bd2dfea4bb7da0794c152fb",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 01f859b..777fde6 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1 +1,3 @@",
+ "+`multi line`",
+ "+`one line`",
+ " `one line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1c977e732d2d54bc59ae6691d06e1ed62856276e"
+ "shas": "eadba66cb97d885739f3686453ed93fc62b92191..ca0bde0a439c7163f90ffc1bab26d92e478ff307"
}
,{
"testCaseDescription": "javascript-template-string-delete-insert-test",
@@ -558,9 +574,19 @@
"filePaths": [
"template-string.js"
],
- "sha1": "1c977e732d2d54bc59ae6691d06e1ed62856276e",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 777fde6..657129f 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1,3 +1,3 @@",
+ "-`multi line`",
+ "+`one line`",
+ " `one line`",
+ " `one line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a7d5d98e3dd6c17cd69e2f159944e86bbbb5b57d"
+ "shas": "ca0bde0a439c7163f90ffc1bab26d92e478ff307..a3a14c9ce30d30111bd78c7b386af50661fca52b"
}
,{
"testCaseDescription": "javascript-template-string-replacement-test",
@@ -835,9 +861,19 @@
"filePaths": [
"template-string.js"
],
- "sha1": "a7d5d98e3dd6c17cd69e2f159944e86bbbb5b57d",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 657129f..777fde6 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1,3 +1,3 @@",
+ "-`one line`",
+ "+`multi line`",
+ " `one line`",
+ " `one line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "25915946c7be6b67c020087c1df3affef492f627"
+ "shas": "a3a14c9ce30d30111bd78c7b386af50661fca52b..a399a38524f70be2dab1dada1b2ca68a46c824dc"
}
,{
"testCaseDescription": "javascript-template-string-delete-replacement-test",
@@ -1080,9 +1116,19 @@
"filePaths": [
"template-string.js"
],
- "sha1": "25915946c7be6b67c020087c1df3affef492f627",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 777fde6..2b8c0dd 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1,3 +1,2 @@",
+ "-`multi line`",
+ "-`one line`",
+ " `one line`",
+ "+`multi line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "306055d34967da8625d9e90a36fb695920513a40"
+ "shas": "a399a38524f70be2dab1dada1b2ca68a46c824dc..6b3a90c35b12bd9740d672836684fcc748793a5c"
}
,{
"testCaseDescription": "javascript-template-string-delete-test",
@@ -1249,9 +1295,17 @@
"filePaths": [
"template-string.js"
],
- "sha1": "306055d34967da8625d9e90a36fb695920513a40",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 2b8c0dd..399f117 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1,2 +1 @@",
+ "-`one line`",
+ " `multi line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "746d7591f68aebc6443c2b7301b056a1b62635fe"
+ "shas": "6b3a90c35b12bd9740d672836684fcc748793a5c..30a0c41d47115adb0e6133f2b347a536a97dc59b"
}
,{
"testCaseDescription": "javascript-template-string-delete-rest-test",
@@ -1329,7 +1383,14 @@
"filePaths": [
"template-string.js"
],
- "sha1": "746d7591f68aebc6443c2b7301b056a1b62635fe",
+ "patch": [
+ "diff --git a/template-string.js b/template-string.js",
+ "index 399f117..e69de29 100644",
+ "--- a/template-string.js",
+ "+++ b/template-string.js",
+ "@@ -1 +0,0 @@",
+ "-`multi line`"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f23716f158172021ba81a7189a8e49480c956764"
+ "shas": "30a0c41d47115adb0e6133f2b347a536a97dc59b..52f50b42f461e7840a4f2f57f62530561ab97768"
}]
diff --git a/test/corpus/json/javascript/ternary.json b/test/corpus/json/javascript/ternary.json
index 1a68c439c..7fce6360f 100644
--- a/test/corpus/json/javascript/ternary.json
+++ b/test/corpus/json/javascript/ternary.json
@@ -97,9 +97,16 @@
"filePaths": [
"ternary.js"
],
- "sha1": "9d404dee54cc476fe531b48dc2da5e29a43486bb",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index e69de29..a62be2e 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -0,0 +1 @@",
+ "+condition ? case1 : case2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a77de3b69914cbea585f1a560a3e561e20cf28e4"
+ "shas": "785493d3bbdebc780e436799269cfe3ecd5bbf77..1e5394377cdd9791083eaf414c452e2cb8b6b547"
}
,{
"testCaseDescription": "javascript-ternary-replacement-insert-test",
@@ -492,9 +499,18 @@
"filePaths": [
"ternary.js"
],
- "sha1": "a77de3b69914cbea585f1a560a3e561e20cf28e4",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index a62be2e..17b4f8e 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1 +1,3 @@",
+ "+x.y = some.condition ? some.case : some.other.case;",
+ "+condition ? case1 : case2;",
+ " condition ? case1 : case2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d2d5c6d48affe0c143fe1127279c9a04ac385dc1"
+ "shas": "1e5394377cdd9791083eaf414c452e2cb8b6b547..98fa20a80981b0a1d0bd753fa4780cf00cff37a2"
}
,{
"testCaseDescription": "javascript-ternary-delete-insert-test",
@@ -1005,9 +1021,19 @@
"filePaths": [
"ternary.js"
],
- "sha1": "d2d5c6d48affe0c143fe1127279c9a04ac385dc1",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index 17b4f8e..aedee54 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1,3 +1,3 @@",
+ "-x.y = some.condition ? some.case : some.other.case;",
+ "+condition ? case1 : case2;",
+ " condition ? case1 : case2;",
+ " condition ? case1 : case2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f862868724dfea2e92f64f78e0103f298d56d2b4"
+ "shas": "98fa20a80981b0a1d0bd753fa4780cf00cff37a2..c4f454f8f233dc5b769f3c33a9a7c385a9e735c1"
}
,{
"testCaseDescription": "javascript-ternary-replacement-test",
@@ -1518,9 +1544,19 @@
"filePaths": [
"ternary.js"
],
- "sha1": "f862868724dfea2e92f64f78e0103f298d56d2b4",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index aedee54..17b4f8e 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1,3 +1,3 @@",
+ "-condition ? case1 : case2;",
+ "+x.y = some.condition ? some.case : some.other.case;",
+ " condition ? case1 : case2;",
+ " condition ? case1 : case2;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "69ff0a31ff6b19f15863dca9486e0ab6087c4069"
+ "shas": "c4f454f8f233dc5b769f3c33a9a7c385a9e735c1..0c31925fbae7f9350166413775fa9fec2e0434e6"
}
,{
"testCaseDescription": "javascript-ternary-delete-replacement-test",
@@ -2070,9 +2106,19 @@
"filePaths": [
"ternary.js"
],
- "sha1": "69ff0a31ff6b19f15863dca9486e0ab6087c4069",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index 17b4f8e..6fa999d 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1,3 +1,2 @@",
+ "-x.y = some.condition ? some.case : some.other.case;",
+ "-condition ? case1 : case2;",
+ " condition ? case1 : case2;",
+ "+x.y = some.condition ? some.case : some.other.case;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b75387874b94e6e592f2e70ef744fa6a34226a7f"
+ "shas": "0c31925fbae7f9350166413775fa9fec2e0434e6..1692cc99588c25ecae57b8dd68e3dd549ffb2907"
}
,{
"testCaseDescription": "javascript-ternary-delete-test",
@@ -2500,9 +2546,17 @@
"filePaths": [
"ternary.js"
],
- "sha1": "b75387874b94e6e592f2e70ef744fa6a34226a7f",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index 6fa999d..b63b46d 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1,2 +1 @@",
+ "-condition ? case1 : case2;",
+ " x.y = some.condition ? some.case : some.other.case;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "32af5d7a4ed1fa479db1b8ebf115dd3c93788d14"
+ "shas": "1692cc99588c25ecae57b8dd68e3dd549ffb2907..401d9a7fba9973bba51744c3bcebdfb16a32ad04"
}
,{
"testCaseDescription": "javascript-ternary-delete-rest-test",
@@ -2699,7 +2753,14 @@
"filePaths": [
"ternary.js"
],
- "sha1": "32af5d7a4ed1fa479db1b8ebf115dd3c93788d14",
+ "patch": [
+ "diff --git a/ternary.js b/ternary.js",
+ "index b63b46d..e69de29 100644",
+ "--- a/ternary.js",
+ "+++ b/ternary.js",
+ "@@ -1 +0,0 @@",
+ "-x.y = some.condition ? some.case : some.other.case;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fa9291d2324f2ca1e6e986a28f002322c5802753"
+ "shas": "401d9a7fba9973bba51744c3bcebdfb16a32ad04..0132d01181719553a7cda6f4d242269546faaa62"
}]
diff --git a/test/corpus/json/javascript/this-expression.json b/test/corpus/json/javascript/this-expression.json
index ac4d17093..96a485470 100644
--- a/test/corpus/json/javascript/this-expression.json
+++ b/test/corpus/json/javascript/this-expression.json
@@ -74,9 +74,16 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "f8073abc47cb34b48625b1088eecc41cf0e51748",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index e69de29..b251f26 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -0,0 +1 @@",
+ "+this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "f2ba76090f4a10b611dc42dbff868c733a27f3fa"
+ "shas": "de56bb89881ee1f97c710b8447f22a479a373692..618c78bcccee5405762867606d7a27bfe59a1bc2"
}
,{
"testCaseDescription": "javascript-this-expression-replacement-insert-test",
@@ -281,9 +288,18 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "f2ba76090f4a10b611dc42dbff868c733a27f3fa",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index b251f26..5804743 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1 +1,3 @@",
+ "+return this;",
+ "+this;",
+ " this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "28351e3040110b3cf20dd7aa549448226ef573e6"
+ "shas": "618c78bcccee5405762867606d7a27bfe59a1bc2..623a175dabd13a76401fa44b6a8b91e8b4b3616b"
}
,{
"testCaseDescription": "javascript-this-expression-delete-insert-test",
@@ -560,9 +576,19 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "28351e3040110b3cf20dd7aa549448226ef573e6",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index 5804743..3c82a23 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1,3 +1,3 @@",
+ "-return this;",
+ "+this;",
+ " this;",
+ " this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "5625066087fbbfe91153fcaca3a32cae9141ef70"
+ "shas": "623a175dabd13a76401fa44b6a8b91e8b4b3616b..53a0f9ff9b4ddcf86bb526f92d25948a54a90a62"
}
,{
"testCaseDescription": "javascript-this-expression-replacement-test",
@@ -839,9 +865,19 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "5625066087fbbfe91153fcaca3a32cae9141ef70",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index 3c82a23..5804743 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1,3 +1,3 @@",
+ "-this;",
+ "+return this;",
+ " this;",
+ " this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "a861ad5a4e80deffe8d3935b28eeacc7a09abaf0"
+ "shas": "53a0f9ff9b4ddcf86bb526f92d25948a54a90a62..3e09935e8f8001936471b730067f5259b79fd3b2"
}
,{
"testCaseDescription": "javascript-this-expression-delete-replacement-test",
@@ -1084,9 +1120,19 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "a861ad5a4e80deffe8d3935b28eeacc7a09abaf0",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index 5804743..81aca89 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1,3 +1,2 @@",
+ "-return this;",
+ "-this;",
+ " this;",
+ "+return this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b10936b0395363ddeda6e8c3dcdc7b2a264c4372"
+ "shas": "3e09935e8f8001936471b730067f5259b79fd3b2..dd8a39e02b053fa07d0c509a2516a4e0f34ab8da"
}
,{
"testCaseDescription": "javascript-this-expression-delete-test",
@@ -1253,9 +1299,17 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "b10936b0395363ddeda6e8c3dcdc7b2a264c4372",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index 81aca89..45c3231 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1,2 +1 @@",
+ "-this;",
+ " return this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e3cc7c1e7bbf10cca54c81c9951e79da794ab7bb"
+ "shas": "dd8a39e02b053fa07d0c509a2516a4e0f34ab8da..289ffca4faf69ef1b1c2d072bd28a22a88fe8e16"
}
,{
"testCaseDescription": "javascript-this-expression-delete-rest-test",
@@ -1333,7 +1387,14 @@
"filePaths": [
"this-expression.js"
],
- "sha1": "e3cc7c1e7bbf10cca54c81c9951e79da794ab7bb",
+ "patch": [
+ "diff --git a/this-expression.js b/this-expression.js",
+ "index 45c3231..e69de29 100644",
+ "--- a/this-expression.js",
+ "+++ b/this-expression.js",
+ "@@ -1 +0,0 @@",
+ "-return this;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "53e3f5fb29923247cf9f931d7662ac6ddb2fc6a0"
+ "shas": "289ffca4faf69ef1b1c2d072bd28a22a88fe8e16..32100dbe7cbc819422359a14ab7495be3254310f"
}]
diff --git a/test/corpus/json/javascript/throw-statement.json b/test/corpus/json/javascript/throw-statement.json
index 64df57d47..2c2ec9338 100644
--- a/test/corpus/json/javascript/throw-statement.json
+++ b/test/corpus/json/javascript/throw-statement.json
@@ -99,9 +99,16 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "f3b243e075c09050d6b896d8240e38144679a57d",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index e69de29..e2fcb67 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -0,0 +1 @@",
+ "+throw new Error(\"uh oh\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "bd9db8d043c11530adc04450c7b5773f1d2b943f"
+ "shas": "5feeb9240c4cfaac7dec387bafe580d79ff959c8..f4f56dd11222632b6dd231901ea27caa19dd049b"
}
,{
"testCaseDescription": "javascript-throw-statement-replacement-insert-test",
@@ -406,9 +413,18 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "bd9db8d043c11530adc04450c7b5773f1d2b943f",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index e2fcb67..c0020c8 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1 +1,3 @@",
+ "+throw new Error(\"oooooops\");",
+ "+throw new Error(\"uh oh\");",
+ " throw new Error(\"uh oh\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0e0f47d8ad0558bd2553619ccfa7f0f8ad9a85e4"
+ "shas": "f4f56dd11222632b6dd231901ea27caa19dd049b..53022b5b1f89288775172d711942c23c6600e7ea"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-insert-test",
@@ -833,9 +849,19 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "0e0f47d8ad0558bd2553619ccfa7f0f8ad9a85e4",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index c0020c8..4644233 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-throw new Error(\"oooooops\");",
+ "+throw new Error(\"uh oh\");",
+ " throw new Error(\"uh oh\");",
+ " throw new Error(\"uh oh\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "85de2e54463e082038e32de3e9e3608917698765"
+ "shas": "53022b5b1f89288775172d711942c23c6600e7ea..f4c157c075f67866be5d801f75c662500a3ffe0d"
}
,{
"testCaseDescription": "javascript-throw-statement-replacement-test",
@@ -1260,9 +1286,19 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "85de2e54463e082038e32de3e9e3608917698765",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index 4644233..c0020c8 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-throw new Error(\"uh oh\");",
+ "+throw new Error(\"oooooops\");",
+ " throw new Error(\"uh oh\");",
+ " throw new Error(\"uh oh\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "9e169c7887f65fe3bdaaf1b0cf0d48e434bb03bf"
+ "shas": "f4c157c075f67866be5d801f75c662500a3ffe0d..958f241f6f3e4321851c930b1408b6c70c78caa7"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-replacement-test",
@@ -1630,9 +1666,19 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "9e169c7887f65fe3bdaaf1b0cf0d48e434bb03bf",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index c0020c8..a1bbf3e 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-throw new Error(\"oooooops\");",
+ "-throw new Error(\"uh oh\");",
+ " throw new Error(\"uh oh\");",
+ "+throw new Error(\"oooooops\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "eafe400f03627180ef1cbf21f739f2ff0dc860df"
+ "shas": "958f241f6f3e4321851c930b1408b6c70c78caa7..f7af002e3c9b8d7d09687a49a12d31f98ba32d19"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-test",
@@ -1874,9 +1920,17 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "eafe400f03627180ef1cbf21f739f2ff0dc860df",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index a1bbf3e..cc3c531 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1,2 +1 @@",
+ "-throw new Error(\"uh oh\");",
+ " throw new Error(\"oooooops\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7a21ed20f00fbdc812d002f8d73de0ea139aa522"
+ "shas": "f7af002e3c9b8d7d09687a49a12d31f98ba32d19..ea612e0a3b13b75a009a60b24db85afe61e73534"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-rest-test",
@@ -1979,7 +2033,14 @@
"filePaths": [
"throw-statement.js"
],
- "sha1": "7a21ed20f00fbdc812d002f8d73de0ea139aa522",
+ "patch": [
+ "diff --git a/throw-statement.js b/throw-statement.js",
+ "index cc3c531..e69de29 100644",
+ "--- a/throw-statement.js",
+ "+++ b/throw-statement.js",
+ "@@ -1 +0,0 @@",
+ "-throw new Error(\"oooooops\");"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "90fa78ee591c70436d12d9a65e5ab236886874d6"
+ "shas": "ea612e0a3b13b75a009a60b24db85afe61e73534..3a1f9b51fe7092afcbd5589b8987d6e91e2100a5"
}]
diff --git a/test/corpus/json/javascript/true.json b/test/corpus/json/javascript/true.json
index c4b05b0ee..efdebd182 100644
--- a/test/corpus/json/javascript/true.json
+++ b/test/corpus/json/javascript/true.json
@@ -74,9 +74,16 @@
"filePaths": [
"true.js"
],
- "sha1": "20d2c012fbfa3774153c1ec275408bafeecfcca9",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index e69de29..4203d4b 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -0,0 +1 @@",
+ "+true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "4789d9a0142916354237099f42d6b88f0c2d2e99"
+ "shas": "e4ca78655510a1ab2e5ceade62c77bd39b3a9599..5d6753ca7b13ffb0a2ae8fbc6c2802f0df420bdc"
}
,{
"testCaseDescription": "javascript-true-replacement-insert-test",
@@ -281,9 +288,18 @@
"filePaths": [
"true.js"
],
- "sha1": "4789d9a0142916354237099f42d6b88f0c2d2e99",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index 4203d4b..65b6323 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1 +1,3 @@",
+ "+return true;",
+ "+true;",
+ " true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "df73cd7d47cd4cf3f908caac7ec01a773c62df05"
+ "shas": "5d6753ca7b13ffb0a2ae8fbc6c2802f0df420bdc..d5b3f9cb8b018c4ec3217ce23bba60ce976121d7"
}
,{
"testCaseDescription": "javascript-true-delete-insert-test",
@@ -560,9 +576,19 @@
"filePaths": [
"true.js"
],
- "sha1": "df73cd7d47cd4cf3f908caac7ec01a773c62df05",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index 65b6323..91e1cfc 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1,3 +1,3 @@",
+ "-return true;",
+ "+true;",
+ " true;",
+ " true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "46d159de4494dab045050f7941d42bfb36e25cc5"
+ "shas": "d5b3f9cb8b018c4ec3217ce23bba60ce976121d7..0f95d640ec3548f65364f95e8204bd1e7ac92093"
}
,{
"testCaseDescription": "javascript-true-replacement-test",
@@ -839,9 +865,19 @@
"filePaths": [
"true.js"
],
- "sha1": "46d159de4494dab045050f7941d42bfb36e25cc5",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index 91e1cfc..65b6323 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1,3 +1,3 @@",
+ "-true;",
+ "+return true;",
+ " true;",
+ " true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0d81dac90113cf185350bba3a71d5c608325003f"
+ "shas": "0f95d640ec3548f65364f95e8204bd1e7ac92093..751ec53c1e7c260a1d8dd6ca3a97b721c66b4d01"
}
,{
"testCaseDescription": "javascript-true-delete-replacement-test",
@@ -1084,9 +1120,19 @@
"filePaths": [
"true.js"
],
- "sha1": "0d81dac90113cf185350bba3a71d5c608325003f",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index 65b6323..48a44d1 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1,3 +1,2 @@",
+ "-return true;",
+ "-true;",
+ " true;",
+ "+return true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6484ee9740e0cdb59d3f8ab3877644e371cf0667"
+ "shas": "751ec53c1e7c260a1d8dd6ca3a97b721c66b4d01..c887bfabde24ba6883a0f5d005d90410e0d0390d"
}
,{
"testCaseDescription": "javascript-true-delete-test",
@@ -1253,9 +1299,17 @@
"filePaths": [
"true.js"
],
- "sha1": "6484ee9740e0cdb59d3f8ab3877644e371cf0667",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index 48a44d1..c1c6922 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1,2 +1 @@",
+ "-true;",
+ " return true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "087fc0349e3fbaba876282869c1104339ccbd22d"
+ "shas": "c887bfabde24ba6883a0f5d005d90410e0d0390d..905bf8f5fbf76c06792709acaffd8b9190a45199"
}
,{
"testCaseDescription": "javascript-true-delete-rest-test",
@@ -1333,7 +1387,14 @@
"filePaths": [
"true.js"
],
- "sha1": "087fc0349e3fbaba876282869c1104339ccbd22d",
+ "patch": [
+ "diff --git a/true.js b/true.js",
+ "index c1c6922..e69de29 100644",
+ "--- a/true.js",
+ "+++ b/true.js",
+ "@@ -1 +0,0 @@",
+ "-return true;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2969c3538fa44b0b9930417f37b669ad53801cd1"
+ "shas": "905bf8f5fbf76c06792709acaffd8b9190a45199..163b832af7eb86fe2d319810d137565e70a924f4"
}]
diff --git a/test/corpus/json/javascript/try-statement.json b/test/corpus/json/javascript/try-statement.json
index 0051b4e7a..4a58d0d43 100644
--- a/test/corpus/json/javascript/try-statement.json
+++ b/test/corpus/json/javascript/try-statement.json
@@ -160,9 +160,16 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "90fa78ee591c70436d12d9a65e5ab236886874d6",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index e69de29..9826f7c 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -0,0 +1 @@",
+ "+try { f; } catch { g; } finally { h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3d4940b1b8a98f96b29b8a0c445506f3f04289e5"
+ "shas": "3a1f9b51fe7092afcbd5589b8987d6e91e2100a5..04e89cbdebc69c9f36d421f5d0d659f992ea0eb9"
}
,{
"testCaseDescription": "javascript-try-statement-replacement-insert-test",
@@ -711,9 +718,18 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "3d4940b1b8a98f96b29b8a0c445506f3f04289e5",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 9826f7c..7befc1c 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1 +1,3 @@",
+ "+try { f; } catch { h; } finally { g; };",
+ "+try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { g; } finally { h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8bed493bdd0364531dcdfb9737b769489e5638c2"
+ "shas": "04e89cbdebc69c9f36d421f5d0d659f992ea0eb9..477a60f5691efb5cb5a92bc21fca69d9124043cf"
}
,{
"testCaseDescription": "javascript-try-statement-delete-insert-test",
@@ -1506,9 +1522,19 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "8bed493bdd0364531dcdfb9737b769489e5638c2",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 7befc1c..94fed9c 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-try { f; } catch { h; } finally { g; };",
+ "+try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { g; } finally { h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1821c2a8e9a1e623ad44b9dee292ecec382ad098"
+ "shas": "477a60f5691efb5cb5a92bc21fca69d9124043cf..b3caa1e2ca9c36a64f26eb1bcb13ae0313670c8b"
}
,{
"testCaseDescription": "javascript-try-statement-replacement-test",
@@ -2301,9 +2327,19 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "1821c2a8e9a1e623ad44b9dee292ecec382ad098",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 94fed9c..7befc1c 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-try { f; } catch { g; } finally { h; };",
+ "+try { f; } catch { h; } finally { g; };",
+ " try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { g; } finally { h; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "0bc2116f248643695f7950dc86ec8bb0692b58ab"
+ "shas": "b3caa1e2ca9c36a64f26eb1bcb13ae0313670c8b..2148f052267ba61fe0924e6eb49b33e0767715c9"
}
,{
"testCaseDescription": "javascript-try-statement-delete-replacement-test",
@@ -2976,9 +3012,19 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "0bc2116f248643695f7950dc86ec8bb0692b58ab",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 7befc1c..8ab70e0 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-try { f; } catch { h; } finally { g; };",
+ "-try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { g; } finally { h; };",
+ "+try { f; } catch { h; } finally { g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e86c0f496bd69d480fa359a97be75f8c2af38c7e"
+ "shas": "2148f052267ba61fe0924e6eb49b33e0767715c9..d45069cac6de6cc64641b935485492fd1b8ddebd"
}
,{
"testCaseDescription": "javascript-try-statement-delete-test",
@@ -3403,9 +3449,17 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "e86c0f496bd69d480fa359a97be75f8c2af38c7e",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 8ab70e0..024f88a 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1,2 +1 @@",
+ "-try { f; } catch { g; } finally { h; };",
+ " try { f; } catch { h; } finally { g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "34d6068089dd6f07368cde629157cf775f081ef1"
+ "shas": "d45069cac6de6cc64641b935485492fd1b8ddebd..b5c850a8cdd8a0342c396c81e695099ab61ef4e0"
}
,{
"testCaseDescription": "javascript-try-statement-delete-rest-test",
@@ -3569,7 +3623,14 @@
"filePaths": [
"try-statement.js"
],
- "sha1": "34d6068089dd6f07368cde629157cf775f081ef1",
+ "patch": [
+ "diff --git a/try-statement.js b/try-statement.js",
+ "index 024f88a..e69de29 100644",
+ "--- a/try-statement.js",
+ "+++ b/try-statement.js",
+ "@@ -1 +0,0 @@",
+ "-try { f; } catch { h; } finally { g; };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "432b804f2c2742a1c3e16957aea653610dc8daeb"
+ "shas": "b5c850a8cdd8a0342c396c81e695099ab61ef4e0..38a4e343f701a84082bcd768e0389e8f827f85af"
}]
diff --git a/test/corpus/json/javascript/type-operator.json b/test/corpus/json/javascript/type-operator.json
index f71b79011..c30e23e57 100644
--- a/test/corpus/json/javascript/type-operator.json
+++ b/test/corpus/json/javascript/type-operator.json
@@ -83,9 +83,16 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "fa9291d2324f2ca1e6e986a28f002322c5802753",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index e69de29..08d2bf5 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -0,0 +1 @@",
+ "+typeof x;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "efe5e62885640427400e25709254995b5fce6d4e"
+ "shas": "0132d01181719553a7cda6f4d242269546faaa62..57023fbb649ca8b26f0f1c82e121ef508349116e"
}
,{
"testCaseDescription": "javascript-type-operator-replacement-insert-test",
@@ -333,9 +340,18 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "efe5e62885640427400e25709254995b5fce6d4e",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index 08d2bf5..8b9c2f4 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1 +1,3 @@",
+ "+x instanceof String;",
+ "+typeof x;",
+ " typeof x;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8a43544e0cd7546189a326228d919bc6bc992077"
+ "shas": "57023fbb649ca8b26f0f1c82e121ef508349116e..9933e14451e53c5bcf8a7d55b2ce626b78c81253"
}
,{
"testCaseDescription": "javascript-type-operator-delete-insert-test",
@@ -670,9 +686,19 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "8a43544e0cd7546189a326228d919bc6bc992077",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index 8b9c2f4..6a5be18 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-x instanceof String;",
+ "+typeof x;",
+ " typeof x;",
+ " typeof x;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "3eb764ed616f7c0d262fa36a527aee1c4b71c43c"
+ "shas": "9933e14451e53c5bcf8a7d55b2ce626b78c81253..e92145581e653212c7afef3c6edac5b99a243a9a"
}
,{
"testCaseDescription": "javascript-type-operator-replacement-test",
@@ -1007,9 +1033,19 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "3eb764ed616f7c0d262fa36a527aee1c4b71c43c",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index 6a5be18..8b9c2f4 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-typeof x;",
+ "+x instanceof String;",
+ " typeof x;",
+ " typeof x;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "96e35966069591cd0944b9f59bc3a67aeaa03f61"
+ "shas": "e92145581e653212c7afef3c6edac5b99a243a9a..c8db5777eaf4621e21460a72b51347db2f040d3d"
}
,{
"testCaseDescription": "javascript-type-operator-delete-replacement-test",
@@ -1311,9 +1347,19 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "96e35966069591cd0944b9f59bc3a67aeaa03f61",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index 8b9c2f4..d438f9f 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-x instanceof String;",
+ "-typeof x;",
+ " typeof x;",
+ "+x instanceof String;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "16ffe15bbea25e4d6a986618daa96cf4fe6515db"
+ "shas": "c8db5777eaf4621e21460a72b51347db2f040d3d..bd9c107414acd6170b2764d2e848579bacdb0e3f"
}
,{
"testCaseDescription": "javascript-type-operator-delete-test",
@@ -1521,9 +1567,17 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "16ffe15bbea25e4d6a986618daa96cf4fe6515db",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index d438f9f..0bf5275 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1,2 +1 @@",
+ "-typeof x;",
+ " x instanceof String;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "761fa9fd2a46beaf52aaa8f03958adba12f3719b"
+ "shas": "bd9c107414acd6170b2764d2e848579bacdb0e3f..9f099fdb1dc747aae4a61b31087eda99a218b8a1"
}
,{
"testCaseDescription": "javascript-type-operator-delete-rest-test",
@@ -1617,7 +1671,14 @@
"filePaths": [
"type-operator.js"
],
- "sha1": "761fa9fd2a46beaf52aaa8f03958adba12f3719b",
+ "patch": [
+ "diff --git a/type-operator.js b/type-operator.js",
+ "index 0bf5275..e69de29 100644",
+ "--- a/type-operator.js",
+ "+++ b/type-operator.js",
+ "@@ -1 +0,0 @@",
+ "-x instanceof String;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "164de6ef1b42af3022bf42e1fdcab480143b06ef"
+ "shas": "9f099fdb1dc747aae4a61b31087eda99a218b8a1..ef3e803a7f48d3ce5e8de0ca9017609664e7ef16"
}]
diff --git a/test/corpus/json/javascript/undefined.json b/test/corpus/json/javascript/undefined.json
index 536a177e8..7a52af5ef 100644
--- a/test/corpus/json/javascript/undefined.json
+++ b/test/corpus/json/javascript/undefined.json
@@ -74,9 +74,16 @@
"filePaths": [
"undefined.js"
],
- "sha1": "f6fdfae045cfc2c5c89dec2ef98091dac6a57099",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index e69de29..c2ca02c 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -0,0 +1 @@",
+ "+undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e5c3c6eb4098f0c972146d4f52c88bd0e680d2fc"
+ "shas": "61695447b9d6c99d6fbee197c961837045e9237b..4934441f9dfeeaa135562268f75a96859b0348ec"
}
,{
"testCaseDescription": "javascript-undefined-replacement-insert-test",
@@ -281,9 +288,18 @@
"filePaths": [
"undefined.js"
],
- "sha1": "e5c3c6eb4098f0c972146d4f52c88bd0e680d2fc",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index c2ca02c..a4352cc 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1 +1,3 @@",
+ "+return undefined;",
+ "+undefined;",
+ " undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "af050e55137515460c064302689707807c89a4f7"
+ "shas": "4934441f9dfeeaa135562268f75a96859b0348ec..bd30c0f337fea623e026c46dd81f07c5bd939c39"
}
,{
"testCaseDescription": "javascript-undefined-delete-insert-test",
@@ -560,9 +576,19 @@
"filePaths": [
"undefined.js"
],
- "sha1": "af050e55137515460c064302689707807c89a4f7",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index a4352cc..52ea257 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1,3 +1,3 @@",
+ "-return undefined;",
+ "+undefined;",
+ " undefined;",
+ " undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "aa93ed4362103cbbf11ad268abc35f06fcc86f4a"
+ "shas": "bd30c0f337fea623e026c46dd81f07c5bd939c39..8933579c6ec5e19655165fdc6dfc67c2f56c6458"
}
,{
"testCaseDescription": "javascript-undefined-replacement-test",
@@ -839,9 +865,19 @@
"filePaths": [
"undefined.js"
],
- "sha1": "aa93ed4362103cbbf11ad268abc35f06fcc86f4a",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index 52ea257..a4352cc 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1,3 +1,3 @@",
+ "-undefined;",
+ "+return undefined;",
+ " undefined;",
+ " undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "2d35d4ac2c64939d0ae46b684e2b9629e9d3f832"
+ "shas": "8933579c6ec5e19655165fdc6dfc67c2f56c6458..d25d4c09aba8b5c49cadb2dccdc776a9f1fbe009"
}
,{
"testCaseDescription": "javascript-undefined-delete-replacement-test",
@@ -1084,9 +1120,19 @@
"filePaths": [
"undefined.js"
],
- "sha1": "2d35d4ac2c64939d0ae46b684e2b9629e9d3f832",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index a4352cc..a16e747 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1,3 +1,2 @@",
+ "-return undefined;",
+ "-undefined;",
+ " undefined;",
+ "+return undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8cea7b06eb430164afcc79b4b925eb59c62fb26a"
+ "shas": "d25d4c09aba8b5c49cadb2dccdc776a9f1fbe009..04a2c6b24a79d6334f7076d6593c15bf9390fc7c"
}
,{
"testCaseDescription": "javascript-undefined-delete-test",
@@ -1253,9 +1299,17 @@
"filePaths": [
"undefined.js"
],
- "sha1": "8cea7b06eb430164afcc79b4b925eb59c62fb26a",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index a16e747..fb505bb 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1,2 +1 @@",
+ "-undefined;",
+ " return undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1f15efe69dffbaec486a0f685719d36fdfa2899e"
+ "shas": "04a2c6b24a79d6334f7076d6593c15bf9390fc7c..8b75a6f10906ce72cbcac5b8460569fc12d1d46a"
}
,{
"testCaseDescription": "javascript-undefined-delete-rest-test",
@@ -1333,7 +1387,14 @@
"filePaths": [
"undefined.js"
],
- "sha1": "1f15efe69dffbaec486a0f685719d36fdfa2899e",
+ "patch": [
+ "diff --git a/undefined.js b/undefined.js",
+ "index fb505bb..e69de29 100644",
+ "--- a/undefined.js",
+ "+++ b/undefined.js",
+ "@@ -1 +0,0 @@",
+ "-return undefined;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "20d2c012fbfa3774153c1ec275408bafeecfcca9"
+ "shas": "8b75a6f10906ce72cbcac5b8460569fc12d1d46a..e4ca78655510a1ab2e5ceade62c77bd39b3a9599"
}]
diff --git a/test/corpus/json/javascript/var-declaration.json b/test/corpus/json/javascript/var-declaration.json
index 8a2393f64..bb1647316 100644
--- a/test/corpus/json/javascript/var-declaration.json
+++ b/test/corpus/json/javascript/var-declaration.json
@@ -99,9 +99,16 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "7ed50d1404aa1f2b612ab1e1ec31c028d7670964",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index e69de29..b506100 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -0,0 +1 @@",
+ "+var x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "6450dec2ba1bd6431b2f2b170c1c3c78756616be"
+ "shas": "3a0405bd7047ac7693031b2b8fc3060c111cc827..ab5d42f4a2d689a4448905b382347800f7d8c0c9"
}
,{
"testCaseDescription": "javascript-var-declaration-replacement-insert-test",
@@ -439,9 +446,18 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "6450dec2ba1bd6431b2f2b170c1c3c78756616be",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index b506100..b08ebfb 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1 +1,3 @@",
+ "+var x, y = {}, z;",
+ "+var x = 1;",
+ " var x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "7874783309c4c0f18968b4b8e42f867ae51f7ed6"
+ "shas": "ab5d42f4a2d689a4448905b382347800f7d8c0c9..c54a7dd6f18d6ff9b1ae61cfbc435bb8f48698f9"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-insert-test",
@@ -903,9 +919,19 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "7874783309c4c0f18968b4b8e42f867ae51f7ed6",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index b08ebfb..adc261e 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1,3 +1,3 @@",
+ "-var x, y = {}, z;",
+ "+var x = 1;",
+ " var x = 1;",
+ " var x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1ef38d699cf50054c2d5c83d8d12e079c2400b67"
+ "shas": "c54a7dd6f18d6ff9b1ae61cfbc435bb8f48698f9..fe6f08e48bcf737ef622d9d18ae7ecb168274987"
}
,{
"testCaseDescription": "javascript-var-declaration-replacement-test",
@@ -1365,9 +1391,19 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "1ef38d699cf50054c2d5c83d8d12e079c2400b67",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index adc261e..b08ebfb 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1,3 +1,3 @@",
+ "-var x = 1;",
+ "+var x, y = {}, z;",
+ " var x = 1;",
+ " var x = 1;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "1155161124bbda2a296197043b5fde7c31dcbbb0"
+ "shas": "fe6f08e48bcf737ef622d9d18ae7ecb168274987..e290ad684f68c0d4ff70e4a3a505ffa93eced8c3"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-replacement-test",
@@ -1801,9 +1837,19 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "1155161124bbda2a296197043b5fde7c31dcbbb0",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index b08ebfb..514f7c4 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1,3 +1,2 @@",
+ "-var x, y = {}, z;",
+ "-var x = 1;",
+ " var x = 1;",
+ "+var x, y = {}, z;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "8180f9cf9df8c2bb0ade9c0fdedc692f79ebb1ce"
+ "shas": "e290ad684f68c0d4ff70e4a3a505ffa93eced8c3..1f92f8cb789fcf43a3de3151f441bf92bf2f6212"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-test",
@@ -2111,9 +2157,17 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "8180f9cf9df8c2bb0ade9c0fdedc692f79ebb1ce",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index 514f7c4..9fc69e2 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1,2 +1 @@",
+ "-var x = 1;",
+ " var x, y = {}, z;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "bfa3955b5136998064be311b616ccad0f245cf08"
+ "shas": "1f92f8cb789fcf43a3de3151f441bf92bf2f6212..97c9ad09f6e9588c444fb049007997105d30b491"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-rest-test",
@@ -2249,7 +2303,14 @@
"filePaths": [
"var-declaration.js"
],
- "sha1": "bfa3955b5136998064be311b616ccad0f245cf08",
+ "patch": [
+ "diff --git a/var-declaration.js b/var-declaration.js",
+ "index 9fc69e2..e69de29 100644",
+ "--- a/var-declaration.js",
+ "+++ b/var-declaration.js",
+ "@@ -1 +0,0 @@",
+ "-var x, y = {}, z;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "817ea011add2e07e6d0d1410269c2882847e4049"
+ "shas": "97c9ad09f6e9588c444fb049007997105d30b491..b7c92617e1bc8e5fbcf483a8ea69e94339a33a4a"
}]
diff --git a/test/corpus/json/javascript/variable.json b/test/corpus/json/javascript/variable.json
index 550fdc701..863b5bef0 100644
--- a/test/corpus/json/javascript/variable.json
+++ b/test/corpus/json/javascript/variable.json
@@ -74,9 +74,16 @@
"filePaths": [
"variable.js"
],
- "sha1": "fc9b2f0c3bbc1743da1d9f7c05b00dce579743dc",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index e69de29..1cf4ad0 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -0,0 +1 @@",
+ "+theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "743e919f5e47aee15e99fb1253761ba85c11fe6a"
+ "shas": "3accaff544c4d4e390ec737b8c076a43e5d56563..49c032f849f019e32d810e49774f40a58f567df8"
}
,{
"testCaseDescription": "javascript-variable-replacement-insert-test",
@@ -281,9 +288,18 @@
"filePaths": [
"variable.js"
],
- "sha1": "743e919f5e47aee15e99fb1253761ba85c11fe6a",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index 1cf4ad0..888855a 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1 +1,3 @@",
+ "+theVar2",
+ "+theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d2080f5440eb73d2825438502db8980c8cbd1df9"
+ "shas": "49c032f849f019e32d810e49774f40a58f567df8..ae375a014a72082ea44bed596598c1e12a348025"
}
,{
"testCaseDescription": "javascript-variable-delete-insert-test",
@@ -558,9 +574,19 @@
"filePaths": [
"variable.js"
],
- "sha1": "d2080f5440eb73d2825438502db8980c8cbd1df9",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index 888855a..60e041c 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1,3 +1,3 @@",
+ "-theVar2",
+ "+theVar;",
+ " theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "70aea979cee3ebc094d51abb4e173eb1d1af4050"
+ "shas": "ae375a014a72082ea44bed596598c1e12a348025..c5b76769a302fcd3a48d68f455a991c01d58a0c5"
}
,{
"testCaseDescription": "javascript-variable-replacement-test",
@@ -835,9 +861,19 @@
"filePaths": [
"variable.js"
],
- "sha1": "70aea979cee3ebc094d51abb4e173eb1d1af4050",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index 60e041c..888855a 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1,3 +1,3 @@",
+ "-theVar;",
+ "+theVar2",
+ " theVar;",
+ " theVar;"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "643423b4dc71e15d75b80071f756f608998cdf58"
+ "shas": "c5b76769a302fcd3a48d68f455a991c01d58a0c5..99fc27128f2bcedf21b589afe5d355c8f01b1673"
}
,{
"testCaseDescription": "javascript-variable-delete-replacement-test",
@@ -1080,9 +1116,19 @@
"filePaths": [
"variable.js"
],
- "sha1": "643423b4dc71e15d75b80071f756f608998cdf58",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index 888855a..fbc7b28 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1,3 +1,2 @@",
+ "-theVar2",
+ "-theVar;",
+ " theVar;",
+ "+theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "e53e6db231bb1f8459397a9fd843c106e4d71856"
+ "shas": "99fc27128f2bcedf21b589afe5d355c8f01b1673..1ec955cdacef1045e39f487523b6b11245f31137"
}
,{
"testCaseDescription": "javascript-variable-delete-test",
@@ -1249,9 +1295,17 @@
"filePaths": [
"variable.js"
],
- "sha1": "e53e6db231bb1f8459397a9fd843c106e4d71856",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index fbc7b28..7276d95 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1,2 +1 @@",
+ "-theVar;",
+ " theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "61bf73809ef6736679d7c9424501710dc1bdadad"
+ "shas": "1ec955cdacef1045e39f487523b6b11245f31137..b64e131430cad9f2e1b958fe3ee4cd577de5381b"
}
,{
"testCaseDescription": "javascript-variable-delete-rest-test",
@@ -1329,7 +1383,14 @@
"filePaths": [
"variable.js"
],
- "sha1": "61bf73809ef6736679d7c9424501710dc1bdadad",
+ "patch": [
+ "diff --git a/variable.js b/variable.js",
+ "index 7276d95..e69de29 100644",
+ "--- a/variable.js",
+ "+++ b/variable.js",
+ "@@ -1 +0,0 @@",
+ "-theVar2"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "81080589255cbb551f9a84c4691635b5fd543c2e"
+ "shas": "b64e131430cad9f2e1b958fe3ee4cd577de5381b..1b8151602239d34159506d5d6e55de712e8c0d10"
}]
diff --git a/test/corpus/json/javascript/void-operator.json b/test/corpus/json/javascript/void-operator.json
index a2bb5713e..592a3226a 100644
--- a/test/corpus/json/javascript/void-operator.json
+++ b/test/corpus/json/javascript/void-operator.json
@@ -92,9 +92,16 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "01c8f3bc964827b93c4f234df17d50755ab361c2",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index e69de29..02aa750 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -0,0 +1 @@",
+ "+void b()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "fbd9bf7e576d1a13d68a7adfb98ecdd884224d44"
+ "shas": "5434e42ccac5d681cef511be2131960ba1884c93..d2c8feb20f4e031a07c804b491cb8cd197207001"
}
,{
"testCaseDescription": "javascript-void-operator-replacement-insert-test",
@@ -371,9 +378,18 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "fbd9bf7e576d1a13d68a7adfb98ecdd884224d44",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index 02aa750..c493dc5 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1 +1,3 @@",
+ "+void c()",
+ "+void b()",
+ " void b()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b29899e9a37e37adf4f81f86e5360c7b14744603"
+ "shas": "d2c8feb20f4e031a07c804b491cb8cd197207001..326fbe86306ade49a42c236b7fee399fdf4bbbf0"
}
,{
"testCaseDescription": "javascript-void-operator-delete-insert-test",
@@ -756,9 +772,19 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "b29899e9a37e37adf4f81f86e5360c7b14744603",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index c493dc5..aae2f63 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-void c()",
+ "+void b()",
+ " void b()",
+ " void b()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ef008ee9324e5a58a7a32a90e1e3a91cd699dd3a"
+ "shas": "326fbe86306ade49a42c236b7fee399fdf4bbbf0..f61550ca1975a2f502e51f68f86b6e68f009af0d"
}
,{
"testCaseDescription": "javascript-void-operator-replacement-test",
@@ -1141,9 +1167,19 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "ef008ee9324e5a58a7a32a90e1e3a91cd699dd3a",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index aae2f63..c493dc5 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1,3 +1,3 @@",
+ "-void b()",
+ "+void c()",
+ " void b()",
+ " void b()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "b2f17819d5364e6eb86f6c985cefc0aec24128a5"
+ "shas": "f61550ca1975a2f502e51f68f86b6e68f009af0d..603c9f8e59b701207a79ca13ab0fb65d37b50457"
}
,{
"testCaseDescription": "javascript-void-operator-delete-replacement-test",
@@ -1476,9 +1512,19 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "b2f17819d5364e6eb86f6c985cefc0aec24128a5",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index c493dc5..738c34a 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1,3 +1,2 @@",
+ "-void c()",
+ "-void b()",
+ " void b()",
+ "+void c()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "96147c757b7d52a89712f2628f70f91fae9da599"
+ "shas": "603c9f8e59b701207a79ca13ab0fb65d37b50457..d92e2722c6444ac458e1eba9620cde9f358bcb18"
}
,{
"testCaseDescription": "javascript-void-operator-delete-test",
@@ -1699,9 +1745,17 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "96147c757b7d52a89712f2628f70f91fae9da599",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index 738c34a..8e9ceba 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1,2 +1 @@",
+ "-void b()",
+ " void c()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c2a98db7116cf058856f63493ebed236bebeb049"
+ "shas": "d92e2722c6444ac458e1eba9620cde9f358bcb18..481a0d93af0bead516e6e6b6e19dbef8697ae903"
}
,{
"testCaseDescription": "javascript-void-operator-delete-rest-test",
@@ -1797,7 +1851,14 @@
"filePaths": [
"void-operator.js"
],
- "sha1": "c2a98db7116cf058856f63493ebed236bebeb049",
+ "patch": [
+ "diff --git a/void-operator.js b/void-operator.js",
+ "index 8e9ceba..e69de29 100644",
+ "--- a/void-operator.js",
+ "+++ b/void-operator.js",
+ "@@ -1 +0,0 @@",
+ "-void c()"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "71f81ec7bab5350490d3ff7f2444799df17938ba"
+ "shas": "481a0d93af0bead516e6e6b6e19dbef8697ae903..2dd315197d728e8efdfc502c8ec48dac3ee8a4b7"
}]
diff --git a/test/corpus/json/javascript/while-statement.json b/test/corpus/json/javascript/while-statement.json
index eea8f8614..d1ab7c349 100644
--- a/test/corpus/json/javascript/while-statement.json
+++ b/test/corpus/json/javascript/while-statement.json
@@ -108,9 +108,16 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "0fb01413d57a0e85053f498b1e91effda758d625",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index e69de29..1ea2800 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -0,0 +1 @@",
+ "+while (a) { b(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "15accab1cbff459dd966234d5e41324f6b68c3ab"
+ "shas": "02fd2e5dc8f8de3c7dfdb7fc35ffa79ecc5a9711..48365cd31ce4a57900b5ca49962d184b15c9f70e"
}
,{
"testCaseDescription": "javascript-while-statement-replacement-insert-test",
@@ -451,9 +458,18 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "15accab1cbff459dd966234d5e41324f6b68c3ab",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index 1ea2800..c322323 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1 +1,3 @@",
+ "+while (b) { a(); };",
+ "+while (a) { b(); };",
+ " while (a) { b(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "ffa21c0ba8dc082acc8e2f981daa18d9a242809e"
+ "shas": "48365cd31ce4a57900b5ca49962d184b15c9f70e..86345f2375bc709f3fc6ea8887e18d1e5060d2e4"
}
,{
"testCaseDescription": "javascript-while-statement-delete-insert-test",
@@ -934,9 +950,19 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "ffa21c0ba8dc082acc8e2f981daa18d9a242809e",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index c322323..ea96716 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-while (b) { a(); };",
+ "+while (a) { b(); };",
+ " while (a) { b(); };",
+ " while (a) { b(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "bc7538da0c7da13df1af66aff6fd30b1aef485d9"
+ "shas": "86345f2375bc709f3fc6ea8887e18d1e5060d2e4..a64a57b19839fdebcbdb61f4a5642a4bdfd48665"
}
,{
"testCaseDescription": "javascript-while-statement-replacement-test",
@@ -1417,9 +1443,19 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "bc7538da0c7da13df1af66aff6fd30b1aef485d9",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index ea96716..c322323 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1,3 +1,3 @@",
+ "-while (a) { b(); };",
+ "+while (b) { a(); };",
+ " while (a) { b(); };",
+ " while (a) { b(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "d5804425450c27201b5dd68b3f6daec9f55ea3d4"
+ "shas": "a64a57b19839fdebcbdb61f4a5642a4bdfd48665..f3fcb2d82f063979f6ef99e5d5a929717c439e1e"
}
,{
"testCaseDescription": "javascript-while-statement-delete-replacement-test",
@@ -1832,9 +1868,19 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "d5804425450c27201b5dd68b3f6daec9f55ea3d4",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index c322323..28f4b21 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1,3 +1,2 @@",
+ "-while (b) { a(); };",
+ "-while (a) { b(); };",
+ " while (a) { b(); };",
+ "+while (b) { a(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c0e8eff109279ff502fa2d79a28f0e61ee86877a"
+ "shas": "f3fcb2d82f063979f6ef99e5d5a929717c439e1e..417ef021cba8565bf05177eee6db64ed17d9a93b"
}
,{
"testCaseDescription": "javascript-while-statement-delete-test",
@@ -2103,9 +2149,17 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "c0e8eff109279ff502fa2d79a28f0e61ee86877a",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index 28f4b21..e185b25 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1,2 +1 @@",
+ "-while (a) { b(); };",
+ " while (b) { a(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "cc6cc438be57072ecb081cd74bcddfa3d8278688"
+ "shas": "417ef021cba8565bf05177eee6db64ed17d9a93b..c8b46cd494ffd16d1119cab7f07db437b173b372"
}
,{
"testCaseDescription": "javascript-while-statement-delete-rest-test",
@@ -2217,7 +2271,14 @@
"filePaths": [
"while-statement.js"
],
- "sha1": "cc6cc438be57072ecb081cd74bcddfa3d8278688",
+ "patch": [
+ "diff --git a/while-statement.js b/while-statement.js",
+ "index e185b25..e69de29 100644",
+ "--- a/while-statement.js",
+ "+++ b/while-statement.js",
+ "@@ -1 +0,0 @@",
+ "-while (b) { a(); };"
+ ],
"gitDir": "test/corpus/repos/javascript",
- "sha2": "c83c4ea2ff4d29ff6ac3b44972b1e00a723d97b3"
+ "shas": "c8b46cd494ffd16d1119cab7f07db437b173b372..a22f0481bc6a70fba4f09d450abc7b2787f85762"
}]
diff --git a/test/corpus/repos/go b/test/corpus/repos/go
index 67c9b2b4c..72b83c0cd 160000
--- a/test/corpus/repos/go
+++ b/test/corpus/repos/go
@@ -1 +1 @@
-Subproject commit 67c9b2b4c39ded2b611f972919a115ed4b8759da
+Subproject commit 72b83c0cd3955c0af628b6cfd369ee028685eeec
diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript
index 9b877906e..ba01e3794 160000
--- a/test/corpus/repos/javascript
+++ b/test/corpus/repos/javascript
@@ -1 +1 @@
-Subproject commit 9b877906e9b09b14f277f4c3058dfc04eca3d222
+Subproject commit ba01e3794a8efa31353fd2d5726c70bb2ad8c6a8
diff --git a/test/corpus/repos/ruby b/test/corpus/repos/ruby
index 457dc7fc9..a8b440ad7 160000
--- a/test/corpus/repos/ruby
+++ b/test/corpus/repos/ruby
@@ -1 +1 @@
-Subproject commit 457dc7fc963751d0adf0ea4eb8934e39ef717e32
+Subproject commit a8b440ad76232e4e95f5a5ed53b9b6604ece8a17
diff --git a/vendor/tree-sitter-parsers b/vendor/tree-sitter-parsers
index 201c8f0a5..75cf569fa 160000
--- a/vendor/tree-sitter-parsers
+++ b/vendor/tree-sitter-parsers
@@ -1 +1 @@
-Subproject commit 201c8f0a59c269c7e150fba93c053c8798c5c641
+Subproject commit 75cf569fa05d368c0a352f1f4b3906ea2931492c