diff --git a/src/Category.hs b/src/Category.hs
index b596088da..0db8996d1 100644
--- a/src/Category.hs
+++ b/src/Category.hs
@@ -13,7 +13,7 @@ data Category
-- | The top-level branch node.
= Program
-- | A node indicating syntax errors.
- | Error
+ | ParseError
-- | A boolean expression.
| Boolean
-- | A bitwise operator.
@@ -240,7 +240,7 @@ instance (StringConv Category Text) where
instance Listable Category where
tiers
= cons0 Program
- \/ cons0 Error
+ \/ cons0 ParseError
\/ cons0 Boolean
\/ cons0 BooleanOperator
\/ cons0 MathOperator
diff --git a/src/DiffSummary.hs b/src/DiffSummary.hs
index 0ec90ba8c..58761ca4b 100644
--- a/src/DiffSummary.hs
+++ b/src/DiffSummary.hs
@@ -16,6 +16,7 @@ import Category as C
import Data.Functor.Both hiding (fst, snd)
import qualified Data.Functor.Both as Both
import Data.Functor.Listable
+import Data.List.NonEmpty (nonEmpty)
import qualified Data.Text as Text
import Data.Text.Listable
import Data.Record
@@ -196,7 +197,7 @@ toTermName source term = case unwrap term of
S.Defer expr -> toTermName' expr
S.AnonymousFunction params _ -> "anonymous" <> paramsToArgNames params
S.Fixed children -> termNameFromChildren term children
- S.Indexed children -> fromMaybe "branch" $ (toCategoryName . category) . extract <$> head children
+ S.Indexed children -> maybe "branch" sconcat (nonEmpty (intersperse ", " (toTermName' <$> children)))
Leaf leaf -> toS leaf
S.Assignment identifier _ -> toTermName' identifier
S.Function identifier _ _ _ -> toTermName' identifier
@@ -231,7 +232,7 @@ toTermName source term = case unwrap term of
-- 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 _ -> termNameFromSource expr
- S.Switch expr _ -> maybe "" toTermName' expr
+ S.Switch exprs _ -> maybe "" toTermName' (fmap snd (unsnoc exprs))
S.Ternary expr _ -> toTermName' expr
S.OperatorAssignment id _ -> toTermName' id
S.Operator _ -> termNameFromSource term
@@ -239,7 +240,7 @@ toTermName source term = case unwrap term of
S.Pair k v -> toKeyName k <> toArgName v
S.Return children -> Text.intercalate ", " (termNameFromSource <$> children)
S.Yield children -> Text.intercalate ", " (termNameFromSource <$> children)
- S.Error _ -> termNameFromSource term
+ S.ParseError _ -> termNameFromSource term
S.If expr _ -> termNameFromSource expr
S.For clauses _ -> termNameFromChildren term clauses
S.While expr _ -> toTermName' expr
@@ -266,7 +267,7 @@ toTermName source term = case unwrap term of
S.Continue expr -> maybe "" toTermName' expr
S.BlockStatement children -> termNameFromChildren term children
S.DefaultCase children -> termNameFromChildren term children
- S.FieldDecl id expr tag -> termNameFromSource id <> (maybe "" (\expr' -> " " <> termNameFromSource expr') expr) <> (maybe "" ((" " <>) . termNameFromSource) tag)
+ S.FieldDecl id expr tag -> termNameFromSource id <> maybe "" (\expr' -> " " <> termNameFromSource expr') expr <> maybe "" ((" " <>) . termNameFromSource) tag
where toTermName' = toTermName source
termNameFromChildren term children = termNameFromRange (unionRangesFrom (range term) (range <$> children))
termNameFromSource term = termNameFromRange (range term)
@@ -328,7 +329,7 @@ termToDiffInfo blob term = case unwrap term of
S.AnonymousFunction _ _ -> LeafInfo C.AnonymousFunction (toTermName' term) (getField $ extract term)
S.Comment _ -> HideInfo
S.Commented cs leaf -> BranchInfo (termToDiffInfo' <$> cs <> maybeToList leaf) (category $ extract term) BCommented
- S.Error _ -> ErrorInfo (getField $ extract term) (toTermName' term)
+ S.ParseError _ -> ErrorInfo (getField $ extract term) (toTermName' term)
_ -> toLeafInfo term
where toTermName' = toTermName blob
termToDiffInfo' = termToDiffInfo blob
@@ -372,7 +373,7 @@ instance HasCategory Category where
Boolean -> "boolean"
DictionaryLiteral -> "dictionary"
C.Comment -> "comment"
- C.Error -> "error"
+ C.ParseError -> "error"
ExpressionStatements -> "expression statements"
C.Assignment -> "assignment"
C.Function -> "function"
diff --git a/src/Info.hs b/src/Info.hs
index b5eaa73b4..a0db54f6b 100644
--- a/src/Info.hs
+++ b/src/Info.hs
@@ -1,5 +1,22 @@
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving #-}
-module Info (Range(..), characterRange, setCharacterRange, Category(..), category, setCategory, Cost(..), cost, setCost, SourceSpan(..), SourcePos(..), SourceSpans(..), SourceText(..), sourceText) where
+module Info
+( Range(..)
+, characterRange
+, setCharacterRange
+, Category(..)
+, category
+, setCategory
+, Cost(..)
+, cost
+, setCost
+, SourceSpan(..)
+, SourcePos(..)
+, SourceSpans(..)
+, sourceSpan
+, setSourceSpan
+, SourceText(..)
+, sourceText
+) where
import Data.Functor.Listable
import Data.Record
@@ -30,12 +47,17 @@ setCategory = setField
cost :: HasField fields Cost => Record fields -> Cost
cost = getField
-sourceText :: HasField fields SourceText => Record fields -> SourceText
-sourceText = getField
-
setCost :: HasField fields Cost => Record fields -> Cost -> Record fields
setCost = setField
+sourceText :: HasField fields SourceText => Record fields -> SourceText
+sourceText = getField
+
+sourceSpan :: HasField fields SourceSpan => Record fields -> SourceSpan
+sourceSpan = getField
+
+setSourceSpan :: HasField fields SourceSpan => Record fields -> SourceSpan -> Record fields
+setSourceSpan = setField
-- Instances
diff --git a/src/Interpreter.hs b/src/Interpreter.hs
index cc14546f9..f48f7fa2a 100644
--- a/src/Interpreter.hs
+++ b/src/Interpreter.hs
@@ -63,7 +63,7 @@ algorithmWithTerms construct t1 t2 = maybe (recursively t1 t2) (fmap annotate) $
S.FunctionCall <$> recursively identifierA identifierB
<*> bySimilarity argsA argsB
(S.Switch exprA casesA, S.Switch exprB casesB) -> Just $
- S.Switch <$> maybeRecursively exprA exprB
+ S.Switch <$> bySimilarity exprA exprB
<*> bySimilarity casesA casesB
(S.Object tyA a, S.Object tyB b) -> Just $
S.Object <$> maybeRecursively tyA tyB
diff --git a/src/Language.hs b/src/Language.hs
index 49527f14f..df2e28703 100644
--- a/src/Language.hs
+++ b/src/Language.hs
@@ -4,7 +4,6 @@ module Language where
import Data.Record
import Info
import Prologue
-import Source
import qualified Syntax as S
import Term
@@ -41,23 +40,6 @@ languageForType mediaType = case mediaType of
".go" -> Just Language.Go
_ -> Nothing
-termConstructor
- :: Source Char -- ^ The source that the term occurs within.
- -> SourceSpan -- ^ The span that the term occupies.
- -> Category -- ^ The node’s Category.
- -> Range -- ^ The character range that the term occupies.
- -> [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ The child nodes of the term.
- -> IO [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ All child nodes (included unnamed productions) of the term as 'IO'. Only use this if you need it.
- -> IO (SyntaxTerm Text '[Range, Category, SourceSpan]) -- ^ The resulting term, in IO.
-termConstructor source sourceSpan category range children _ =
- withDefaultInfo $ case (category, children) of
- (Error, _) -> S.Error children
- (_, []) -> S.Leaf (toText $ slice range source)
- _ -> S.Indexed children
- where
- withDefaultInfo syntax =
- pure $! cofree ((range :. category :. sourceSpan :. Nil) :< syntax)
-
toVarDecl :: (HasField fields Category) => Term (S.Syntax Text) (Record fields) -> Term (S.Syntax Text) (Record fields)
toVarDecl child = cofree $ setCategory (extract child) VarDecl :< S.VarDecl child Nothing
diff --git a/src/Language/C.hs b/src/Language/C.hs
index 313752222..ce759c92a 100644
--- a/src/Language/C.hs
+++ b/src/Language/C.hs
@@ -1,28 +1,19 @@
{-# LANGUAGE DataKinds #-}
module Language.C where
-import Data.Record
import Info
import Prologue
import Source
import qualified Syntax as S
import Term
-termConstructor
- :: Source Char -- ^ The source that the term occurs within.
- -> SourceSpan -- ^ The span that the term occupies.
- -> Category -- ^ The node’s Category.
- -> Range -- ^ The character range that the term occupies.
+termAssignment
+ :: Source Char -- ^ The source of the term.
+ -> Category -- ^ The category for the term.
-> [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ The child nodes of the term.
- -> IO [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ All child nodes (included unnamed productions) of the term as 'IO'. Only use this if you need it.
- -> IO (SyntaxTerm Text '[Range, Category, SourceSpan]) -- ^ The resulting term, in IO.
-termConstructor source sourceSpan category range children _
- | category == Error = withDefaultInfo (S.Error children)
- | otherwise = withDefaultInfo $ case children of
- [] -> S.Leaf . toText $ slice range source
- _ -> S.Indexed children
- where
- withDefaultInfo syntax = pure $! cofree ((range :. category :. sourceSpan :. Nil) :< syntax)
+ -> Maybe (S.Syntax Text (SyntaxTerm Text '[Range, Category, SourceSpan])) -- ^ The resulting term, in Maybe.
+termAssignment _ _ _ = Nothing
+
categoryForCProductionName :: Text -> Category
categoryForCProductionName = Other
diff --git a/src/Language/Go.hs b/src/Language/Go.hs
index a79c3d48c..609b7518f 100644
--- a/src/Language/Go.hs
+++ b/src/Language/Go.hs
@@ -6,243 +6,72 @@ import Info
import Source
import Term
import qualified Syntax as S
-import Data.Record
-import Range (unionRangesFrom)
-import SourceSpan (unionSourceSpansFrom)
-termConstructor
- :: Source Char -- ^ The source that the term occurs within.
- -> SourceSpan -- ^ The span that the term occupies.
- -> Category -- ^ The node’s Category.
- -> Range -- ^ The character range that the term occupies.
+termAssignment
+ :: Source Char -- ^ The source of the term.
+ -> Category -- ^ The category for the term.
-> [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ The child nodes of the term.
- -> IO [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ All child nodes (included unnamed productions) of the term as 'IO'. Only use this if you need it.
- -> IO (SyntaxTerm Text '[Range, Category, SourceSpan]) -- ^ The resulting term, in IO.
-termConstructor source sourceSpan category range children _ = pure $! case category of
- Return -> withDefaultInfo $ S.Return children
- Module -> case Prologue.break (\node -> Info.category (extract node) == Other "package_clause") children of
- (comments, packageName : rest) -> case unwrap packageName of
- S.Indexed [id] ->
- let module' = withCategory Module (S.Module id rest)
- in withCategory Program (S.Indexed (comments <> [module']))
- _ -> withRanges range Error children (S.Error children)
- _ -> withRanges range Error children (S.Error children)
- Other "import_declaration" -> toImports children
- Function -> withDefaultInfo $ case children of
- [id, params, block] -> S.Function id (toList $ unwrap params) Nothing (toList $ unwrap block)
- [id, params, ty, block] -> S.Function id (toList $ unwrap params) (Just ty) (toList $ unwrap block)
- rest -> S.Error rest
- For ->
- withDefaultInfo $ case children of
- [body] | Info.category (extract body) == Other "block" ->
- S.For [] (toList $ unwrap body)
- [forClause, body] | Info.category (extract forClause) == Other "for_clause" ->
- S.For (toList $ unwrap forClause) (toList $ unwrap body)
- [rangeClause, body] | Info.category (extract rangeClause) == Other "range_clause" ->
- S.For (toList $ unwrap rangeClause) (toList $ unwrap body)
- other -> S.Error other
- TypeDecl -> toTypeDecl children
- StructTy -> toStructTy children
- FieldDecl -> toFieldDecl children
- Switch ->
- case Prologue.break isCaseClause children of
- (clauses, cases) -> withDefaultInfo $ case clauses of
- [id] -> S.Switch (Just id) cases -- type_switch_statement
- [] -> S.Switch Nothing (toCase <$> cases)
- _ -> S.Switch (Just (withCategory ExpressionStatements (S.Indexed clauses))) (toCase <$> cases)
- where
- isCaseClause = (== Case) . Info.category . extract
- toCase clause = case toList (unwrap clause) of
- clause' : rest -> case toList (unwrap clause') of
- [clause''] -> withCategory Case $ S.Case clause'' rest
- [] -> withCategory DefaultCase $ S.DefaultCase rest
- rest -> withCategory Error $ S.Error rest
- [] -> withCategory Error $ S.Error [clause]
- ParameterDecl -> withDefaultInfo $ case children of
- [param, ty] -> S.ParameterDecl (Just ty) param
- [param] -> S.ParameterDecl Nothing param
- _ -> S.Error children
- Assignment -> toVarAssignment children
- Select -> withDefaultInfo $ S.Select (toCommunicationCase =<< children)
- where toCommunicationCase = toList . unwrap
- Go -> withDefaultInfo $ toExpression S.Go children
- Defer -> withDefaultInfo $ toExpression S.Defer children
- SubscriptAccess -> withDefaultInfo $ toSubscriptAccess children
- IndexExpression -> withDefaultInfo $ toSubscriptAccess children
- Slice -> sliceToSubscriptAccess children
- Other "composite_literal" -> toLiteral children
- TypeAssertion -> withDefaultInfo $ case children of
- [a, b] -> S.TypeAssertion a b
- rest -> S.Error rest
- TypeConversion -> withDefaultInfo $ case children of
- [a, b] -> S.TypeConversion a b
- rest -> S.Error rest
+ -> Maybe (S.Syntax Text (SyntaxTerm Text '[Range, Category, SourceSpan])) -- ^ The resulting term, in Maybe.
+termAssignment source category children = case (category, children) of
+ (Module, [moduleName]) -> Just $ S.Module moduleName []
+ (Import, [importName]) -> Just $ S.Import importName []
+ (Function, [id, params, block]) -> Just $ S.Function id (toList (unwrap params)) Nothing (toList (unwrap block))
+ (Function, [id, params, ty, block]) -> Just $ S.Function id (toList (unwrap params)) (Just ty) (toList (unwrap block))
+ (For, [body]) | Other "block" <- Info.category (extract body) -> Just $ S.For [] (toList (unwrap body))
+ (For, [forClause, body]) | Other "for_clause" <- Info.category (extract forClause) -> Just $ S.For (toList (unwrap forClause)) (toList (unwrap body))
+ (For, [rangeClause, body]) | Other "range_clause" <- Info.category (extract rangeClause) -> Just $ S.For (toList (unwrap rangeClause)) (toList (unwrap body))
+ (TypeDecl, [identifier, ty]) -> Just $ S.TypeDecl identifier ty
+ (StructTy, _) -> Just (S.Ty children)
+ (FieldDecl, [idList])
+ | [ident] <- toList (unwrap idList)
+ -> Just (S.FieldDecl ident Nothing Nothing)
+ (FieldDecl, [idList, ty])
+ | [ident] <- toList (unwrap idList)
+ -> Just $ case Info.category (extract ty) of
+ StringLiteral -> S.FieldDecl ident Nothing (Just ty)
+ _ -> S.FieldDecl ident (Just ty) Nothing
+ (FieldDecl, [idList, ty, tag])
+ | [ident] <- toList (unwrap idList)
+ -> Just (S.FieldDecl ident (Just ty) (Just tag))
+ (ParameterDecl, param : ty) -> Just $ S.ParameterDecl (listToMaybe ty) param
+ (Assignment, [identifier, expression]) -> Just $ S.VarAssignment identifier expression
+ (Select, _) -> Just $ S.Select (children >>= toList . unwrap)
+ (Go, [expr]) -> Just $ S.Go expr
+ (Defer, [expr]) -> Just $ S.Defer expr
+ (SubscriptAccess, [a, b]) -> Just $ S.SubscriptAccess a b
+ (IndexExpression, [a, b]) -> Just $ S.SubscriptAccess a b
+ (Slice, [a, rest]) -> Just $ S.SubscriptAccess a rest
+ (Other "composite_literal", [ty, values])
+ | ArrayTy <- Info.category (extract ty)
+ -> Just $ S.Array (Just ty) (toList (unwrap values))
+ | DictionaryTy <- Info.category (extract ty)
+ -> Just $ S.Object (Just ty) (toList (unwrap values))
+ | SliceTy <- Info.category (extract ty)
+ -> Just $ S.SubscriptAccess ty values
+ (Other "composite_literal", []) -> Just $ S.Struct Nothing []
+ (Other "composite_literal", [ty]) -> Just $ S.Struct (Just ty) []
+ (Other "composite_literal", [ty, values]) -> Just $ S.Struct (Just ty) (toList (unwrap values))
+ (TypeAssertion, [a, b]) -> Just $ S.TypeAssertion a b
+ (TypeConversion, [a, b]) -> Just $ S.TypeConversion a b
-- TODO: Handle multiple var specs
- Other "var_declaration" -> toVarDecls children
- VarAssignment -> toVarAssignment children
- VarDecl -> toVarAssignment children
- If -> toIfStatement children
- FunctionCall -> withDefaultInfo $ case children of
- [id] -> S.FunctionCall id []
- id : rest -> S.FunctionCall id rest
- rest -> S.Error rest
- Other "const_declaration" -> toConsts children
- AnonymousFunction -> withDefaultInfo $ case children of
- [params, _, body] -> case toList (unwrap params) of
- [params'] -> S.AnonymousFunction (toList $ unwrap params') (toList $ unwrap body)
- rest -> S.Error rest
- rest -> S.Error rest
- PointerTy -> withDefaultInfo $ case children of
- [ty] -> S.Ty ty
- rest -> S.Error rest
- ChannelTy -> withDefaultInfo $ case children of
- [ty] -> S.Ty ty
- rest -> S.Error rest
- Send -> withDefaultInfo $ case children of
- [channel, expr] -> S.Send channel expr
- rest -> S.Error rest
- Operator -> withDefaultInfo $ S.Operator children
- FunctionTy ->
- let params = withRanges range Params children $ S.Indexed children
- in withDefaultInfo $ S.Ty params
- IncrementStatement ->
- withDefaultInfo $ S.Leaf . toText $ slice range source
- DecrementStatement ->
- withDefaultInfo $ S.Leaf . toText $ slice range source
- QualifiedIdentifier ->
- withDefaultInfo $ S.Leaf . toText $ slice range source
- Break -> toBreak children
- Continue -> toContinue children
- Pair -> toPair children
- Method -> toMethod children
- _ -> withDefaultInfo $ case children of
- [] -> S.Leaf . toText $ slice range source
- _ -> S.Indexed children
- where
- toMethod = \case
- [params, name, fun] -> withDefaultInfo (S.Method name Nothing (toList $ unwrap params) (toList $ unwrap fun))
- [params, name, outParams, fun] ->
- let params' = toList (unwrap params)
- outParams' = toList (unwrap outParams)
- allParams = params' <> outParams'
- in withDefaultInfo (S.Method name Nothing allParams (toList $ unwrap fun))
- [params, name, outParams, ty, fun] ->
- let params' = toList (unwrap params)
- outParams' = toList (unwrap outParams)
- allParams = params' <> outParams'
- in withDefaultInfo (S.Method name (Just ty) allParams (toList $ unwrap fun))
- rest -> withCategory Error (S.Error rest)
- toPair = \case
- [key, value] -> withDefaultInfo (S.Pair key value)
- rest -> withCategory Error (S.Error rest)
- toBreak = \case
- [label] -> withDefaultInfo (S.Break (Just label))
- [] -> withDefaultInfo (S.Break Nothing)
- rest -> withCategory Error (S.Error rest)
- toContinue = \case
- [label] -> withDefaultInfo (S.Continue (Just label))
- [] -> withDefaultInfo (S.Continue Nothing)
- rest -> withCategory Error (S.Error rest)
-
- toStructTy children =
- withDefaultInfo (S.Ty (withRanges range FieldDeclarations children (S.Indexed children)))
-
- toLiteral = \case
- children@[ty, _] -> case Info.category (extract ty) of
- ArrayTy -> toImplicitArray children
- DictionaryTy -> toMap children
- SliceTy -> sliceToSubscriptAccess children
- _ -> toStruct children
- rest -> withRanges range Error rest $ S.Error rest
- toImplicitArray = \case
- [ty, values] -> withCategory ArrayLiteral (S.Array (Just ty) (toList $ unwrap values))
- rest -> withRanges range Error rest $ S.Error rest
- toMap = \case
- [ty, values] -> withCategory DictionaryLiteral (S.Object (Just ty) (toList $ unwrap values))
- rest -> withRanges range Error rest $ S.Error rest
- toStruct = \case
- [] -> withCategory Struct (S.Struct Nothing [])
- [ty] -> withCategory Struct (S.Struct (Just ty) [])
- [ty, values] -> withCategory Struct (S.Struct (Just ty) (toList $ unwrap values))
- rest -> withRanges range Error rest $ S.Error rest
- toFieldDecl = \case
- [idList, ty] ->
- case Info.category (extract ty) of
- StringLiteral -> withCategory FieldDecl (S.FieldDecl (toIdent (toList (unwrap idList))) Nothing (Just ty))
- _ -> withCategory FieldDecl (S.FieldDecl (toIdent (toList (unwrap idList))) (Just ty) Nothing)
- [idList] ->
- withCategory FieldDecl (S.FieldDecl (toIdent (toList (unwrap idList))) Nothing Nothing)
- [idList, ty, tag] ->
- withCategory FieldDecl (S.FieldDecl (toIdent (toList (unwrap idList))) (Just ty) (Just tag))
- rest -> withRanges range Error rest (S.Error rest)
-
- where
- toIdent = \case
- [ident] -> ident
- rest -> withRanges range Error rest (S.Error rest)
-
-
- toExpression f = \case
- [expr] -> f expr
- rest -> S.Error rest
- toSubscriptAccess = \case
- [a, b] -> S.SubscriptAccess a b
- rest -> S.Error rest
- sliceToSubscriptAccess = \case
- a : rest ->
- let sliceElement = withRanges range Element rest $ S.Fixed rest
- in withCategory Slice (S.SubscriptAccess a sliceElement)
- rest -> withRanges range Error rest $ S.Error rest
-
- toIfStatement children = case Prologue.break ((Other "block" ==) . Info.category . extract) children of
- (clauses, blocks) ->
- let clauses' = withRanges range ExpressionStatements clauses (S.Indexed clauses)
- blocks' = foldMap (toList . unwrap) blocks
- in withDefaultInfo (S.If clauses' blocks')
-
- toTypeDecl = \case
- [identifier, ty] -> withDefaultInfo $ S.TypeDecl identifier ty
- rest -> withRanges range Error rest $ S.Error rest
-
- toImports imports =
- withDefaultInfo $ S.Indexed (imports >>= toImport)
- where
- toImport i = case toList (unwrap i) of
- [importName] -> [ withCategory Import (S.Import importName []) ]
- rest@(_:_) -> [ withRanges range Error rest (S.Error rest)]
- [] -> []
-
- toVarDecls children = withDefaultInfo (S.Indexed children)
-
- toConsts constSpecs = withDefaultInfo (S.Indexed constSpecs)
-
- toVarAssignment = \case
- [idList, ty] | Info.category (extract ty) == Identifier ->
- let ids = toList (unwrap idList)
- idList' = (\id -> withRanges range VarDecl [id] (S.VarDecl id (Just ty))) <$> ids
- in withRanges range ExpressionStatements idList' (S.Indexed idList')
- [idList, expressionList] | Info.category (extract expressionList) == Other "expression_list" ->
- let assignments' = zipWith (\id expr ->
- withCategory VarAssignment $ S.VarAssignment id expr)
- (toList $ unwrap idList) (toList $ unwrap expressionList)
- in withRanges range ExpressionStatements assignments' (S.Indexed assignments')
- [idList, _, expressionList] ->
- let assignments' = zipWith (\id expr ->
- withCategory VarAssignment $ S.VarAssignment id expr) (toList $ unwrap idList) (toList $ unwrap expressionList)
- in withRanges range ExpressionStatements assignments' (S.Indexed assignments')
- [idList] -> withDefaultInfo (S.Indexed [idList])
- rest -> withRanges range Error rest (S.Error rest)
-
- withRanges originalRange category' terms syntax =
- let ranges' = getField . extract <$> terms
- sourceSpans' = getField . extract <$> terms
- in
- cofree ((unionRangesFrom originalRange ranges' :. category' :. unionSourceSpansFrom sourceSpan sourceSpans' :. Nil) :< syntax)
-
- withCategory category syntax =
- cofree ((range :. category :. sourceSpan :. Nil) :< syntax)
-
- withDefaultInfo = withCategory category
+ (VarAssignment, [identifier, expression]) -> Just $ S.VarAssignment identifier expression
+ (VarDecl, [idList, ty]) | Identifier <- Info.category (extract ty) -> Just $ S.VarDecl idList (Just ty)
+ (FunctionCall, id : rest) -> Just $ S.FunctionCall id rest
+ (AnonymousFunction, [params, _, body])
+ | [params'] <- toList (unwrap params)
+ -> Just $ S.AnonymousFunction (toList (unwrap params')) (toList (unwrap body))
+ (PointerTy, _) -> Just $ S.Ty children
+ (ChannelTy, _) -> Just $ S.Ty children
+ (Send, [channel, expr]) -> Just $ S.Send channel expr
+ (Operator, _) -> Just $ S.Operator children
+ (FunctionTy, _) -> Just $ S.Ty children
+ (IncrementStatement, _) -> Just $ S.Leaf $ toText source
+ (DecrementStatement, _) -> Just $ S.Leaf $ toText source
+ (QualifiedIdentifier, _) -> Just $ S.Leaf $ toText source
+ (Method, [params, name, fun]) -> Just (S.Method name Nothing (toList (unwrap params)) (toList (unwrap fun)))
+ (Method, [params, name, outParams, fun]) -> Just (S.Method name Nothing (toList (unwrap params) <> toList (unwrap outParams)) (toList (unwrap fun)))
+ (Method, [params, name, outParams, ty, fun]) -> Just (S.Method name (Just ty) (toList (unwrap params) <> toList (unwrap outParams)) (toList (unwrap fun)))
+ _ -> Nothing
categoryForGoName :: Text -> Category
categoryForGoName = \case
@@ -265,7 +94,8 @@ categoryForGoName = \case
"var_spec" -> VarAssignment
"const_spec" -> VarAssignment
"assignment_statement" -> Assignment
- "source_file" -> Module
+ "source_file" -> Program
+ "package_clause" -> Module
"if_statement" -> If
"for_statement" -> For
"expression_switch_statement" -> Switch
@@ -294,7 +124,6 @@ categoryForGoName = \case
"channel_type" -> ChannelTy
"send_statement" -> Send
"unary_expression" -> Operator
- "ERROR" -> Error
"function_type" -> FunctionTy
"inc_statement" -> IncrementStatement
"dec_statement" -> DecrementStatement
@@ -303,4 +132,6 @@ categoryForGoName = \case
"continue_statement" -> Continue
"rune_literal" -> RuneLiteral
"method_declaration" -> Method
+ "import_spec" -> Import
+ "block" -> ExpressionStatements
s -> Other (toS s)
diff --git a/src/Language/JavaScript.hs b/src/Language/JavaScript.hs
index 7db8d6d25..0f253ee43 100644
--- a/src/Language/JavaScript.hs
+++ b/src/Language/JavaScript.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE DataKinds #-}
module Language.JavaScript where
-import Data.Record
import Info
import Prologue
import Source
@@ -9,104 +8,60 @@ import Language
import qualified Syntax as S
import Term
-operators :: [Category]
-operators = [ Operator, BooleanOperator, MathOperator, RelationalOperator, BitwiseOperator ]
-
-termConstructor
- :: Source Char -- ^ The source that the term occurs within.
- -> SourceSpan -- ^ The span that the term occupies.
- -> Category -- ^ The node’s Category.
- -> Range -- ^ The character range that the term occupies.
+termAssignment
+ :: Source Char -- ^ The source of the term.
+ -> Category -- ^ The category for the term.
-> [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ The child nodes of the term.
- -> IO [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ All child nodes (included unnamed productions) of the term as 'IO'. Only use this if you need it.
- -> IO (SyntaxTerm Text '[Range, Category, SourceSpan]) -- ^ The resulting term, in IO.
-termConstructor source sourceSpan category range children allChildren
- | category == Error = withDefaultInfo (S.Error children)
- | category `elem` operators = do
- allChildren' <- allChildren
- withDefaultInfo $ S.Operator allChildren'
- | otherwise = withDefaultInfo $ case (category, children) of
- (Return, _) -> S.Return children
- (Assignment, [ identifier, value ]) -> S.Assignment identifier value
- (Assignment, _ ) -> S.Error children
- (MathAssignment, [ identifier, value ]) -> S.OperatorAssignment identifier value
- (MathAssignment, _ ) -> S.Error children
- (MemberAccess, [ base, property ]) -> S.MemberAccess base property
- (MemberAccess, _ ) -> S.Error children
- (SubscriptAccess, [ base, element ]) -> S.SubscriptAccess base element
- (SubscriptAccess, _ ) -> S.Error children
- (CommaOperator, [ a, b ]) -> case unwrap b of
- S.Indexed rest -> S.Indexed $ a : rest
- _ -> S.Indexed children
- (CommaOperator, _ ) -> S.Error children
- (FunctionCall, _) -> case children of
- member : args | Info.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
- (VarAssignment, [ x, y ]) -> S.VarAssignment x y
- (VarAssignment, _ ) -> S.Error children
- (VarDecl, _) -> S.Indexed $ toVarDecl <$> children
- (Switch, expr : rest) -> S.Switch (Just expr) rest
- (Switch, _ ) -> S.Error children
- (Case, [ expr, body ]) -> S.Case expr [body]
- (Case, _ ) -> S.Error children
- (Object, _) -> S.Object Nothing $ foldMap toTuple children
- (Pair, _) -> S.Fixed children
- (Comment, _) -> S.Comment . toText $ slice range source
- (If, expr : rest ) -> S.If expr rest
- (If, _ ) -> S.Error children
- (While, expr : rest ) -> S.While expr rest
- (While, _ ) -> S.Error children
- (DoWhile, [ expr, body ]) -> S.DoWhile expr body
- (DoWhile, _ ) -> S.Error children
- (Throw, [ expr ]) -> S.Throw expr
- (Throw, _ ) -> S.Error children
- (Constructor, [ expr ]) -> S.Constructor expr
- (Constructor, _ ) -> S.Error children
- (Try, _) -> case children of
- [ body ] -> S.Try [body] [] Nothing Nothing
- [ body, catch ] | Catch <- Info.category (extract catch) -> S.Try [body] [catch] Nothing Nothing
- [ body, finally ] | Finally <- Info.category (extract finally) -> S.Try [body] [] Nothing (Just finally)
- [ body, catch, finally ]
- | Catch <- Info.category (extract catch)
- , Finally <- Info.category (extract finally) -> S.Try [body] [catch] Nothing (Just finally)
- _ -> S.Error children
- (ArrayLiteral, _) -> S.Array Nothing children
- (Method, [ identifier, params, exprs ]) -> S.Method identifier Nothing (toList (unwrap params)) (toList (unwrap exprs))
- (Method, [ identifier, exprs ]) -> S.Method identifier Nothing [] (toList (unwrap exprs))
- (Method, _ ) -> S.Error children
- (Class, [ identifier, superclass, definitions ]) -> S.Class identifier (Just superclass) (toList (unwrap definitions))
- (Class, [ identifier, definitions ]) -> S.Class identifier Nothing (toList (unwrap definitions))
- (Class, _ ) -> S.Error children
- (Import, [ statements, identifier ] ) -> S.Import identifier (toList (unwrap statements))
- (Import, [ identifier ] ) -> S.Import identifier []
- (Import, _ ) -> S.Error children
- (Export, [ statements, identifier] ) -> S.Export (Just identifier) (toList (unwrap statements))
- (Export, [ statements ] ) -> case unwrap statements of
- S.Indexed _ -> S.Export Nothing (toList (unwrap statements))
- _ -> S.Export (Just statements) []
- (Export, _ ) -> S.Error children
- (Break, [ expr ] ) -> S.Break (Just expr)
- (Yield, _ ) -> S.Yield children
- (For, _) -> case unsnoc children of
- Just (exprs, body) -> S.For exprs [body]
- _ -> S.Error children
- (Function, _) -> case children of
- [ body ] -> S.AnonymousFunction [] [body]
- [ params, body ] -> S.AnonymousFunction (toList (unwrap params)) [body]
- [ id, params, body ] -> S.Function id (toList (unwrap params)) Nothing [body]
- _ -> S.Error children
- (_, []) -> S.Leaf . toText $ slice range source
- _ -> S.Indexed children
- where
- withDefaultInfo syntax =
- pure $! case syntax of
- S.MethodCall{} -> cofree ((range :. MethodCall :. sourceSpan :. Nil) :< syntax)
- _ -> cofree ((range :. category :. sourceSpan :. Nil) :< syntax)
+ -> Maybe (S.Syntax Text (SyntaxTerm Text '[Range, Category, SourceSpan])) -- ^ The resulting term, in Maybe.
+termAssignment _ category children
+ = case (category, children) of
+ (Assignment, [ identifier, value ]) -> Just $ S.Assignment identifier value
+ (MathAssignment, [ identifier, value ]) -> Just $ S.OperatorAssignment identifier value
+ (MemberAccess, [ base, property ]) -> Just $ S.MemberAccess base property
+ (SubscriptAccess, [ base, element ]) -> Just $ S.SubscriptAccess base element
+ (CommaOperator, [ a, b ])
+ | S.Indexed rest <- unwrap b
+ -> Just $ S.Indexed $ a : rest
+ (FunctionCall, member : args)
+ | S.MemberAccess target method <- unwrap member
+ -> Just $ S.MethodCall target method (toList . unwrap =<< args)
+ (FunctionCall, function : args) -> Just $ S.FunctionCall function (toList . unwrap =<< args)
+ (Ternary, condition : cases) -> Just $ S.Ternary condition cases
+ (VarAssignment, [ x, y ]) -> Just $ S.VarAssignment x y
+ (VarDecl, _) -> Just . S.Indexed $ toVarDecl <$> children
+ (Object, _) -> Just . S.Object Nothing $ foldMap toTuple children
+ (DoWhile, [ expr, body ]) -> Just $ S.DoWhile expr body
+ (Constructor, [ expr ]) -> Just $ S.Constructor expr
+ (Try, [ body ]) -> Just $ S.Try [body] [] Nothing Nothing
+ (Try, [ body, catch ])
+ | Catch <- Info.category (extract catch)
+ -> Just $ S.Try [body] [catch] Nothing Nothing
+ (Try, [ body, finally ])
+ | Finally <- Info.category (extract finally)
+ -> Just $ S.Try [body] [] Nothing (Just finally)
+ (Try, [ body, catch, finally ])
+ | Catch <- Info.category (extract catch)
+ , Finally <- Info.category (extract finally)
+ -> Just $ S.Try [body] [catch] Nothing (Just finally)
+ (ArrayLiteral, _) -> Just $ S.Array Nothing children
+ (Method, [ identifier, params, exprs ]) -> Just $ S.Method identifier Nothing (toList (unwrap params)) (toList (unwrap exprs))
+ (Method, [ identifier, exprs ]) -> Just $ S.Method identifier Nothing [] (toList (unwrap exprs))
+ (Class, [ identifier, superclass, definitions ]) -> Just $ S.Class identifier (Just superclass) (toList (unwrap definitions))
+ (Class, [ identifier, definitions ]) -> Just $ S.Class identifier Nothing (toList (unwrap definitions))
+ (Import, [ statements, identifier ] ) -> Just $ S.Import identifier (toList (unwrap statements))
+ (Import, [ identifier ] ) -> Just $ S.Import identifier []
+ (Export, [ statements, identifier] ) -> Just $ S.Export (Just identifier) (toList (unwrap statements))
+ (Export, [ statements ] )
+ | S.Indexed _ <- unwrap statements
+ -> Just $ S.Export Nothing (toList (unwrap statements))
+ | otherwise -> Just $ S.Export (Just statements) []
+ (For, _)
+ | Just (exprs, body) <- unsnoc children
+ -> Just $ S.For exprs [body]
+ (Function, [ body ]) -> Just $ S.AnonymousFunction [] [body]
+ (Function, [ params, body ]) -> Just $ S.AnonymousFunction (toList (unwrap params)) [body]
+ (Function, [ id, params, body ]) -> Just $ S.Function id (toList (unwrap params)) Nothing [body]
+ _ -> Nothing
categoryForJavaScriptProductionName :: Text -> Category
categoryForJavaScriptProductionName name = case name of
@@ -138,7 +93,6 @@ categoryForJavaScriptProductionName name = case name of
"trailing_if_statement" -> If
"empty_statement" -> Empty
"program" -> Program
- "ERROR" -> Error
"function_call" -> FunctionCall
"pair" -> Pair
"string" -> StringLiteral
diff --git a/src/Language/Ruby.hs b/src/Language/Ruby.hs
index c6cff83b3..ec2057376 100644
--- a/src/Language/Ruby.hs
+++ b/src/Language/Ruby.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE DataKinds #-}
module Language.Ruby where
-import Data.Record
import Data.List (partition)
import Info
import Prologue
@@ -10,35 +9,22 @@ import Language
import qualified Syntax as S
import Term
-operators :: [Category]
-operators = [ Binary, Unary, RangeExpression, ScopeOperator ]
-
-termConstructor
- :: Source Char -- ^ The source that the term occurs within.
- -> SourceSpan -- ^ The span that the term occupies.
- -> Category -- ^ The node’s Category.
- -> Range -- ^ The character range that the term occupies.
+termAssignment
+ :: Source Char -- ^ The source of the term.
+ -> Category -- ^ The category for the term.
-> [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ The child nodes of the term.
- -> IO [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ All child nodes (included unnamed productions) of the term as 'IO'. Only use this if you need it.
- -> IO (SyntaxTerm Text '[Range, Category, SourceSpan]) -- ^ The resulting term, in IO.
-termConstructor source sourceSpan category range children allChildren
- | category == Error = pure $! withDefaultInfo (S.Error children)
- | category `elem` operators = do
- allChildren' <- allChildren
- pure $! withDefaultInfo $ S.Operator allChildren'
- | otherwise = pure . withDefaultInfo $ case (category, children) of
- (ArgumentPair, [ k, v ] ) -> S.Pair k v
- (ArgumentPair, _ ) -> S.Error children
- (KeywordParameter, [ k, v ] ) -> S.Pair k v
+ -> Maybe (S.Syntax Text (SyntaxTerm Text '[Range, Category, SourceSpan])) -- ^ The resulting term, in Maybe.
+termAssignment _ category children
+ = case (category, children) of
+ (ArgumentPair, [ k, v ] ) -> Just $ S.Pair k v
+ (KeywordParameter, [ k, v ] ) -> Just $ S.Pair k v
-- NB: ("keyword_parameter", k) is a required keyword parameter, e.g.:
-- def foo(name:); end
-- Let it fall through to generate an Indexed syntax.
- (OptionalParameter, [ k, v ] ) -> S.Pair k v
- (OptionalParameter, _ ) -> S.Error children
- (ArrayLiteral, _ ) -> S.Array Nothing children
- (Assignment, [ identifier, value ]) -> S.Assignment identifier value
- (Assignment, _ ) -> S.Error children
- (Begin, _ ) -> case partition (\x -> Info.category (extract x) == Rescue) children of
+ (OptionalParameter, [ k, v ] ) -> Just $ S.Pair k v
+ (ArrayLiteral, _ ) -> Just $ S.Array Nothing children
+ (Assignment, [ identifier, value ]) -> Just $ S.Assignment identifier value
+ (Begin, _ ) -> Just $ case partition (\x -> Info.category (extract x) == Rescue) children of
(rescues, rest) -> case partition (\x -> Info.category (extract x) == Ensure || Info.category (extract x) == Else) rest of
(ensureElse, body) -> case ensureElse of
[ elseBlock, ensure ]
@@ -50,84 +36,59 @@ termConstructor source sourceSpan category range children allChildren
[ elseBlock ] | Else <- Info.category (extract elseBlock) -> S.Try body rescues (Just elseBlock) Nothing
[ ensure ] | Ensure <- Info.category (extract ensure) -> S.Try body rescues Nothing (Just ensure)
_ -> S.Try body rescues Nothing Nothing
- (Case, expr : body ) -> S.Switch (Just expr) body
- (Case, _ ) -> S.Error children
- (When, condition : body ) -> S.Case condition body
- (When, _ ) -> S.Error children
- (Class, constant : rest ) -> case rest of
- ( superclass : body ) | Superclass <- Info.category (extract superclass) -> S.Class constant (Just superclass) body
- _ -> S.Class constant Nothing rest
- (Class, _ ) -> S.Error children
- (SingletonClass, identifier : rest ) -> S.Class identifier Nothing rest
- (SingletonClass, _ ) -> S.Error children
- (Comment, _ ) -> S.Comment . toText $ slice range source
- (Ternary, condition : cases) -> S.Ternary condition cases
- (Ternary, _ ) -> S.Error children
- (Constant, _ ) -> S.Fixed children
- (MethodCall, _ ) -> case children of
- member : args | MemberAccess <- Info.category (extract member) -> 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
- (Other "lambda", _) -> case children of
- [ body ] -> S.AnonymousFunction [] [body]
- ( params : body ) -> S.AnonymousFunction (toList (unwrap params)) body
- _ -> S.Error children
- (Object, _ ) -> S.Object Nothing $ foldMap toTuple children
- (Modifier If, [ lhs, condition ]) -> S.If condition [lhs]
- (Modifier If, _) -> S.Error children
- (If, condition : body ) -> S.If condition body
- (If, _ ) -> S.Error children
- (Modifier Unless, [lhs, rhs]) -> S.If (withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)) [lhs]
- (Modifier Unless, _) -> S.Error children
- (Unless, expr : rest) -> S.If (withRecord (setCategory (extract expr) Negate) (S.Negate expr)) rest
- (Unless, _) -> S.Error children
- (Modifier Until, [ lhs, rhs ]) -> S.While (withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)) [lhs]
- (Modifier Until, _) -> S.Error children
- (Until, expr : rest) -> S.While (withRecord (setCategory (extract expr) Negate) (S.Negate expr)) rest
- (Until, _) -> S.Error children
- (Elsif, condition : body ) -> S.If condition body
- (Elsif, _ ) -> S.Error children
- (SubscriptAccess, [ base, element ]) -> S.SubscriptAccess base element
- (SubscriptAccess, _ ) -> S.Error children
- (For, lhs : expr : rest ) -> S.For [lhs, expr] rest
- (For, _ ) -> S.Error children
- (OperatorAssignment, [ identifier, value ]) -> S.OperatorAssignment identifier value
- (OperatorAssignment, _ ) -> S.Error children
- (MemberAccess, [ base, property ]) -> S.MemberAccess base property
- (MemberAccess, _ ) -> S.Error children
- (Method, _ ) -> case children of
- identifier : params : body | Params <- Info.category (extract params) -> S.Method identifier Nothing (toList (unwrap params)) body
- identifier : body -> S.Method identifier Nothing [] body
- _ -> S.Error children
- (Module, constant : body ) -> S.Module constant body
- (Module, _ ) -> S.Error children
- (Modifier Rescue, [lhs, rhs] ) -> S.Rescue [lhs] [rhs]
- (Modifier Rescue, _) -> S.Error children
- (Rescue, _ ) -> case children of
- exceptions : exceptionVar : rest
- | RescueArgs <- Info.category (extract exceptions)
- , RescuedException <- Info.category (extract exceptionVar) -> S.Rescue (toList (unwrap exceptions) <> [exceptionVar]) rest
- exceptionVar : rest | RescuedException <- Info.category (extract exceptionVar) -> S.Rescue [exceptionVar] rest
- exceptions : body | RescueArgs <- Info.category (extract exceptions) -> S.Rescue (toList (unwrap exceptions)) body
- body -> S.Rescue [] body
- (Return, _ ) -> S.Return children
- (Modifier While, [ lhs, condition ]) -> S.While condition [lhs]
- (Modifier While, _) -> S.Error children
- (While, expr : rest ) -> S.While expr rest
- (While, _ ) -> S.Error children
- (Yield, _ ) -> S.Yield children
- _ | category `elem` [ BeginBlock, EndBlock ] -> S.BlockStatement children
- (_, []) -> S.Leaf . toText $ slice range source
- _ -> S.Indexed children
+ (Class, constant : superclass : body)
+ | Superclass <- Info.category (extract superclass)
+ -> Just $ S.Class constant (Just superclass) body
+ (Class, constant : rest) -> Just $ S.Class constant Nothing rest
+ (SingletonClass, identifier : rest) -> Just $ S.Class identifier Nothing rest
+ (Case, _) -> Just $ uncurry S.Switch (Prologue.break ((== When) . Info.category . extract) children)
+ (When, expr : body) -> Just $ S.Case expr body
+ (Ternary, condition : cases) -> Just $ S.Ternary condition cases
+ (Constant, _ ) -> Just $ S.Fixed children
+ (MethodCall, fn : args)
+ | MemberAccess <- Info.category (extract fn)
+ , [target, method] <- toList (unwrap fn)
+ -> Just $ S.MethodCall target method (toList . unwrap =<< args)
+ | otherwise
+ -> Just $ S.FunctionCall fn (toList . unwrap =<< args)
+ (Other "lambda", first : rest)
+ | null rest -> Just $ S.AnonymousFunction [] [first]
+ | otherwise -> Just $ S.AnonymousFunction (toList (unwrap first)) rest
+ (Object, _ ) -> Just . S.Object Nothing $ foldMap toTuple children
+ (Modifier If, [ lhs, condition ]) -> Just $ S.If condition [lhs]
+ (Modifier Unless, [lhs, rhs]) -> Just $ S.If (withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)) [lhs]
+ (Unless, expr : rest) -> Just $ S.If (withRecord (setCategory (extract expr) Negate) (S.Negate expr)) rest
+ (Modifier Until, [ lhs, rhs ]) -> Just $ S.While (withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)) [lhs]
+ (Until, expr : rest) -> Just $ S.While (withRecord (setCategory (extract expr) Negate) (S.Negate expr)) rest
+ (Elsif, condition : body ) -> Just $ S.If condition body
+ (SubscriptAccess, [ base, element ]) -> Just $ S.SubscriptAccess base element
+ (For, lhs : expr : rest ) -> Just $ S.For [lhs, expr] rest
+ (OperatorAssignment, [ identifier, value ]) -> Just $ S.OperatorAssignment identifier value
+ (MemberAccess, [ base, property ]) -> Just $ S.MemberAccess base property
+ (Method, identifier : rest)
+ | params : body <- rest
+ , Params <- Info.category (extract params)
+ -> Just $ S.Method identifier Nothing (toList (unwrap params)) body
+ | otherwise
+ -> Just $ S.Method identifier Nothing [] rest
+ (Module, constant : body ) -> Just $ S.Module constant body
+ (Modifier Rescue, [lhs, rhs] ) -> Just $ S.Rescue [lhs] [rhs]
+ (Rescue, exceptions : exceptionVar : rest)
+ | RescueArgs <- Info.category (extract exceptions)
+ , RescuedException <- Info.category (extract exceptionVar)
+ -> Just $ S.Rescue (toList (unwrap exceptions) <> [exceptionVar]) rest
+ (Rescue, exceptionVar : rest)
+ | RescuedException <- Info.category (extract exceptionVar)
+ -> Just $ S.Rescue [exceptionVar] rest
+ (Rescue, exceptions : body)
+ | RescueArgs <- Info.category (extract exceptions)
+ -> Just $ S.Rescue (toList (unwrap exceptions)) body
+ (Rescue, body) -> Just $ S.Rescue [] body
+ (Modifier While, [ lhs, condition ]) -> Just $ S.While condition [lhs]
+ _ | category `elem` [ BeginBlock, EndBlock ] -> Just $ S.BlockStatement children
+ _ -> Nothing
where
withRecord record syntax = cofree (record :< syntax)
- withCategory category syntax =
- cofree ((range :. category :. sourceSpan :. Nil) :< syntax)
- withDefaultInfo syntax = case syntax of
- S.MethodCall{} -> withCategory MethodCall syntax
- _ -> withCategory category syntax
categoryForRubyName :: Text -> Category
categoryForRubyName = \case
@@ -151,7 +112,6 @@ categoryForRubyName = \case
"elsif" -> Elsif
"end_block" -> EndBlock
"ensure" -> Ensure
- "ERROR" -> Error
"exception_variable" -> RescuedException
"exceptions" -> RescueArgs
"false" -> Boolean
diff --git a/src/Range.hs b/src/Range.hs
index 73cb4b2b2..cdbe313a0 100644
--- a/src/Range.hs
+++ b/src/Range.hs
@@ -2,6 +2,7 @@ module Range where
import qualified Data.Char as Char
import Data.List (span)
+import Data.List.NonEmpty (nonEmpty)
import Data.Semigroup
import Data.String
import Prologue
@@ -60,17 +61,9 @@ intersectionRange range1 range2 = Range (max (start range1) (start range2)) (min
unionRange :: Range -> Range -> Range
unionRange (Range start1 end1) (Range start2 end2) = Range (min start1 start2) (max end1 end2)
--- | Return a range that contains all the ranges in a Foldable, or Range 0 0 if it’s empty.
-unionRanges :: Foldable f => f Range -> Range
-unionRanges = unionRangesFrom (Range 0 0)
-
--- | Return Just the concatenation of any elements in a Foldable, or Nothing if it is empty.
-maybeConcat :: (Foldable f, Semigroup a) => f a -> Maybe a
-maybeConcat = getOption . foldMap (Option . Just)
-
-- | Return a range that contains all the ranges in a Foldable, or the passed Range if the Foldable is empty.
unionRangesFrom :: Foldable f => Range -> f Range -> Range
-unionRangesFrom range = fromMaybe range . maybeConcat
+unionRangesFrom range = maybe range sconcat . nonEmpty . toList
-- Instances
diff --git a/src/Renderer/JSON.hs b/src/Renderer/JSON.hs
index f4ad2d664..22bf8830e 100644
--- a/src/Renderer/JSON.hs
+++ b/src/Renderer/JSON.hs
@@ -119,7 +119,7 @@ syntaxToTermField syntax = case syntax of
S.Pair a b -> childrenFields [a, b]
S.Comment _ -> []
S.Commented comments child -> childrenFields (comments <> maybeToList child)
- S.Error c -> childrenFields c
+ S.ParseError c -> childrenFields c
S.For expressions body -> [ "expressions" .= expressions ] <> [ "body" .= body ]
S.DoWhile expression body -> [ "expression" .= expression ] <> [ "body" .= body ]
S.While expression body -> [ "expression" .= expression ] <> [ "body" .= body ]
diff --git a/src/Renderer/Split.hs b/src/Renderer/Split.hs
index 4d660766e..a48d3cbd3 100644
--- a/src/Renderer/Split.hs
+++ b/src/Renderer/Split.hs
@@ -33,7 +33,7 @@ classifyMarkup category element = (element !) . A.class_ . textValue $ styleName
styleName :: Category -> Text
styleName category = "category-" <> case category of
Program -> "program"
- C.Error -> "error"
+ C.ParseError -> "error"
BooleanOperator -> "boolean_operator"
MathOperator -> "math_operator"
BitwiseOperator -> "bitwise_operator"
diff --git a/src/SourceSpan.hs b/src/SourceSpan.hs
index 514d68b5b..12dfe3594 100644
--- a/src/SourceSpan.hs
+++ b/src/SourceSpan.hs
@@ -8,6 +8,7 @@ module SourceSpan where
import Data.Aeson ((.=), (.:))
import qualified Data.Aeson as A
+import Data.List.NonEmpty (nonEmpty)
import Data.Semigroup
import Data.These
import Prologue
@@ -55,13 +56,7 @@ displayStartEndPos sp =
displaySourcePos (spanStart sp) <> " - " <> displaySourcePos (spanEnd sp)
unionSourceSpansFrom :: Foldable f => SourceSpan -> f SourceSpan -> SourceSpan
-unionSourceSpansFrom sourceSpan = fromMaybe sourceSpan . maybeConcat
-
-maybeConcat :: (Foldable f, Semigroup a) => f a -> Maybe a
-maybeConcat = getOption . foldMap (Option . Just)
-
-unionSourceSpans :: Foldable f => f SourceSpan -> SourceSpan
-unionSourceSpans = unionSourceSpansFrom emptySourceSpan
+unionSourceSpansFrom sourceSpan = maybe sourceSpan sconcat . nonEmpty . toList
unionSourceSpan :: SourceSpan -> SourceSpan -> SourceSpan
unionSourceSpan (SourceSpan start1 end1) (SourceSpan start2 end2) = SourceSpan (min start1 start2) (max end1 end2)
diff --git a/src/Syntax.hs b/src/Syntax.hs
index 3418bd65d..1a85263e9 100644
--- a/src/Syntax.hs
+++ b/src/Syntax.hs
@@ -45,7 +45,7 @@ data Syntax a f
-- | A subscript access contains a syntax, and another syntax that indefies a property or value in the first syntax.
-- | e.g. in Javascript x["y"] represents a subscript access syntax.
| SubscriptAccess { subscriptId :: f, subscriptElement :: f }
- | Switch { switchExpr :: (Maybe f), cases :: [f] }
+ | Switch { switchExpr :: [f], cases :: [f] }
| Case { caseExpr :: f, caseStatements :: [f] }
-- | A default case in a switch statement.
| DefaultCase [f]
@@ -57,7 +57,7 @@ data Syntax a f
| Comment a
-- | A term preceded or followed by any number of comments.
| Commented [f] (Maybe f)
- | Error [f]
+ | ParseError [f]
-- | A for statement has a list of expressions to setup the iteration and then a list of expressions in the body.
| For [f] [f]
| DoWhile { doWhileBody :: f, doWhileExpr :: f }
@@ -101,7 +101,7 @@ data Syntax a f
-- | A field declaration with an optional type, and an optional tag.
| FieldDecl f (Maybe f) (Maybe f)
-- | A type.
- | Ty f
+ | Ty [f]
-- | A send statement has a channel and an expression in Go.
| Send f f
deriving (Eq, Foldable, Functor, Generic, Generic1, Mergeable, Ord, Show, Traversable, ToJSON)
@@ -133,7 +133,7 @@ instance Listable2 Syntax where
\/ liftCons2 recur recur Pair
\/ liftCons1 leaf Comment
\/ liftCons2 (liftTiers recur) (liftTiers recur) Commented
- \/ liftCons1 (liftTiers recur) Syntax.Error
+ \/ liftCons1 (liftTiers recur) Syntax.ParseError
\/ liftCons2 (liftTiers recur) (liftTiers recur) For
\/ liftCons2 recur recur DoWhile
\/ liftCons2 recur (liftTiers recur) While
@@ -161,7 +161,7 @@ instance Listable2 Syntax where
\/ liftCons2 (liftTiers recur) recur ParameterDecl
\/ liftCons2 recur recur TypeDecl
\/ liftCons3 recur (liftTiers recur) (liftTiers recur) FieldDecl
- \/ liftCons1 recur Ty
+ \/ liftCons1 (liftTiers recur) Ty
\/ liftCons2 recur recur Send
\/ liftCons1 (liftTiers recur) DefaultCase
diff --git a/src/TreeSitter.hs b/src/TreeSitter.hs
index 57661ee37..378e6b56c 100644
--- a/src/TreeSitter.hs
+++ b/src/TreeSitter.hs
@@ -1,5 +1,8 @@
{-# LANGUAGE DataKinds #-}
-module TreeSitter (treeSitterParser) where
+module TreeSitter
+( treeSitterParser
+, defaultTermAssignment
+) where
import Prologue hiding (Constructor)
import Category
@@ -15,6 +18,8 @@ import Source
import qualified Syntax
import Foreign
import Foreign.C.String
+import qualified Syntax as S
+import Term
import Text.Parser.TreeSitter hiding (Language(..))
import qualified Text.Parser.TreeSitter as TS
import SourceSpan
@@ -56,23 +61,73 @@ documentToTerm language document SourceBlob{..} = alloca $ \ root -> do
-- Without it, we may not evaluate the value until after we’ve exited
-- the scope that `node` was allocated within, meaning `alloca` will
-- free it & other stack data may overwrite it.
- range `seq` sourceSpan `seq` termConstructor source sourceSpan (categoryForLanguageProductionName language (toS name)) range children allChildren
+ range `seq` sourceSpan `seq` assignTerm language (slice range source) (range :. categoryForLanguageProductionName language (toS name) :. sourceSpan :. Nil) children allChildren
getChild node n out = ts_node_p_named_child node n out >> toTerm out
{-# INLINE getChild #-}
getUnnamedChild node n out = ts_node_p_child node n out >> toTerm out
{-# INLINE getUnnamedChild #-}
- termConstructor = case language of
- JavaScript -> JS.termConstructor
- C -> C.termConstructor
- Language.Go -> Go.termConstructor
- Ruby -> Ruby.termConstructor
- _ -> Language.termConstructor
isNonEmpty child = category (extract child) /= Empty
+assignTerm :: Language -> Source Char -> Record '[Range, Category, SourceSpan] -> [ SyntaxTerm Text '[ Range, Category, SourceSpan ] ] -> IO [ SyntaxTerm Text '[ Range, Category, SourceSpan ] ] -> IO (SyntaxTerm Text '[ Range, Category, SourceSpan ])
+assignTerm language source annotation children allChildren =
+ cofree . (annotation :<) <$> case assignTermByLanguage language source (category annotation) children of
+ Just a -> pure a
+ _ -> defaultTermAssignment source (category annotation) children allChildren
+ where assignTermByLanguage :: Language -> Source Char -> Category -> [ SyntaxTerm Text '[ Range, Category, SourceSpan ] ] -> Maybe (S.Syntax Text (SyntaxTerm Text '[ Range, Category, SourceSpan ]))
+ assignTermByLanguage = \case
+ JavaScript -> JS.termAssignment
+ C -> C.termAssignment
+ Language.Go -> Go.termAssignment
+ Ruby -> Ruby.termAssignment
+ _ -> \ _ _ _ -> Nothing
+
+defaultTermAssignment :: Source Char -> Category -> [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -> IO [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -> IO (S.Syntax Text (SyntaxTerm Text '[Range, Category, SourceSpan]))
+defaultTermAssignment source category children allChildren
+ | category `elem` operatorCategories = S.Operator <$> allChildren
+ | otherwise = pure $! case (category, children) of
+ (ParseError, children) -> S.ParseError children
+
+ (Comment, _) -> S.Comment (toText source)
+
+ (Pair, [key, value]) -> S.Pair key value
+
+ -- Control flow statements
+ (If, condition : body) -> S.If condition body
+ (Switch, _) -> uncurry S.Switch (Prologue.break ((== Case) . Info.category . extract) children)
+ (Case, expr : body) -> S.Case expr body
+ (While, expr : rest) -> S.While expr rest
+
+ -- Statements
+ (Return, _) -> S.Return children
+ (Yield, _) -> S.Yield children
+ (Throw, [expr]) -> S.Throw expr
+ (Break, [label]) -> S.Break (Just label)
+ (Break, []) -> S.Break Nothing
+ (Continue, [label]) -> S.Continue (Just label)
+ (Continue, []) -> S.Continue Nothing
+
+ (_, []) -> S.Leaf (toText source)
+ (_, children) -> S.Indexed children
+ where operatorCategories =
+ [ Operator
+ , Binary
+ , Unary
+ , RangeExpression
+ , ScopeOperator
+ , BooleanOperator
+ , MathOperator
+ , RelationalOperator
+ , BitwiseOperator
+ ]
+
+
categoryForLanguageProductionName :: Language -> Text -> Category
-categoryForLanguageProductionName = \case
+categoryForLanguageProductionName = withDefaults . \case
JavaScript -> JS.categoryForJavaScriptProductionName
C -> C.categoryForCProductionName
Ruby -> Ruby.categoryForRubyName
Language.Go -> Go.categoryForGoName
_ -> Other
+ where withDefaults productionMap = \case
+ "ERROR" -> ParseError
+ s -> productionMap s
diff --git a/test/corpus/diff-summaries/go/array-types.json b/test/corpus/diff-summaries/go/array-types.json
index c24c8ca46..e66f3c14e 100644
--- a/test/corpus/diff-summaries/go/array-types.json
+++ b/test/corpus/diff-summaries/go/array-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "2a8d9f01f7c78b4014cc0cf0057b991673c39dd0..2c7a579aacd6880fb8754faf1c5344053d1c2d0f"
+ "shas": "26a0f67120f1cf6fc8e13694d29195177fe1040e..c78b61e9c9b8281f97e59c9c8f20975e41409ed6"
}
,{
"testCaseDescription": "go-array-types-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'a' type declaration in the main function"
}
]
},
@@ -81,7 +96,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "2c7a579aacd6880fb8754faf1c5344053d1c2d0f..ec664b52de32519f5ab8e36f4574394f41e4b355"
+ "shas": "c78b61e9c9b8281f97e59c9c8f20975e41409ed6..2309b08e406723f9c132aa816d302bf8cc88ed71"
}
,{
"testCaseDescription": "go-array-types-replacement-test",
@@ -190,7 +205,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ec664b52de32519f5ab8e36f4574394f41e4b355..faa453789421465ab0581edc344b9b587d4a6085"
+ "shas": "2309b08e406723f9c132aa816d302bf8cc88ed71..c474dfe7ba478f742c76c8ad39a8ea012b94cd0a"
}
,{
"testCaseDescription": "go-array-types-delete-replacement-test",
@@ -299,7 +314,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "faa453789421465ab0581edc344b9b587d4a6085..28c283b6b69d706d24fa6797e8132b3dc19f77fb"
+ "shas": "c474dfe7ba478f742c76c8ad39a8ea012b94cd0a..00ced47bbecee34a07334faeb92f0093e2de599f"
}
,{
"testCaseDescription": "go-array-types-delete-insert-test",
@@ -319,7 +334,7 @@
]
}
},
- "summary": "Deleted the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'a' type declaration in the main function"
}
]
},
@@ -342,7 +357,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "28c283b6b69d706d24fa6797e8132b3dc19f77fb..b48fc843a07daf06dcd9a8eebb418c6e6c5a3eb0"
+ "shas": "00ced47bbecee34a07334faeb92f0093e2de599f..5ef5fdfe7d8f7c1cd02153ff01390ec3a5261233"
}
,{
"testCaseDescription": "go-array-types-teardown-test",
@@ -357,12 +372,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -384,5 +414,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b48fc843a07daf06dcd9a8eebb418c6e6c5a3eb0..50b59edcf73e7686cbfc6db242bf00346aebcf11"
+ "shas": "5ef5fdfe7d8f7c1cd02153ff01390ec3a5261233..242b339cd8dd07d6f1232ff7f96ee2eb324516d9"
}]
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 e139962dc..8fde74c71 100644
--- a/test/corpus/diff-summaries/go/array-with-implicit-length.json
+++ b/test/corpus/diff-summaries/go/array-with-implicit-length.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ce81a7d517fc9a2808b223f5e2ec2b77fd6fad64..500b648128cc717a6a3abe3c3aa11fc82556659e"
+ "shas": "576026694b333d8935d7a3e88a32dbd0ed0b3fa4..e880dbc369823d4b5c4e1643d1301395af59040b"
}
,{
"testCaseDescription": "go-array-with-implicit-length-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a1' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'a1' var assignment in the main function"
}
]
},
@@ -81,7 +96,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "500b648128cc717a6a3abe3c3aa11fc82556659e..bc51671fc62602f0d5a1e399a8cd0cdd272507dd"
+ "shas": "e880dbc369823d4b5c4e1643d1301395af59040b..b5893374f1fc215bc0e9639fbff6745b22594bc0"
}
,{
"testCaseDescription": "go-array-with-implicit-length-replacement-test",
@@ -101,7 +116,7 @@
]
}
},
- "summary": "Added '4' in the [...]int array of the 'main' function"
+ "summary": "Added '4' in the [...]int composite_literal of the 'main' function"
},
{
"span": {
@@ -128,7 +143,7 @@
}
]
},
- "summary": "Replaced '1' with '5' in the [...]int array of the 'main' function"
+ "summary": "Replaced '1' with '5' in the [...]int composite_literal of the 'main' function"
},
{
"span": {
@@ -143,7 +158,7 @@
]
}
},
- "summary": "Added '6' in the [...]int array of the 'main' function"
+ "summary": "Added '6' in the [...]int composite_literal of the 'main' function"
},
{
"span": {
@@ -158,7 +173,7 @@
]
}
},
- "summary": "Deleted '2' in the [...]int array of the 'main' function"
+ "summary": "Deleted '2' in the [...]int composite_literal of the 'main' function"
},
{
"span": {
@@ -173,7 +188,7 @@
]
}
},
- "summary": "Deleted '3' in the [...]int array of the 'main' function"
+ "summary": "Deleted '3' in the [...]int composite_literal of the 'main' function"
}
]
},
@@ -196,7 +211,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "bc51671fc62602f0d5a1e399a8cd0cdd272507dd..6a2f0882912e58d2f3e34875a6bb44804d586279"
+ "shas": "b5893374f1fc215bc0e9639fbff6745b22594bc0..235fa8a9d47005f230e6db96c1d2bf4d8e935851"
}
,{
"testCaseDescription": "go-array-with-implicit-length-delete-replacement-test",
@@ -216,7 +231,7 @@
]
}
},
- "summary": "Added '1' in the [...]int array of the 'main' function"
+ "summary": "Added '1' in the [...]int composite_literal of the 'main' function"
},
{
"span": {
@@ -231,7 +246,7 @@
]
}
},
- "summary": "Added '2' in the [...]int array of the 'main' function"
+ "summary": "Added '2' in the [...]int composite_literal of the 'main' function"
},
{
"span": {
@@ -246,7 +261,7 @@
]
}
},
- "summary": "Added '3' in the [...]int array of the 'main' function"
+ "summary": "Added '3' in the [...]int composite_literal of the 'main' function"
},
{
"span": {
@@ -261,7 +276,7 @@
]
}
},
- "summary": "Deleted '4' in the [...]int array of the 'main' function"
+ "summary": "Deleted '4' in the [...]int composite_literal of the 'main' function"
},
{
"span": {
@@ -276,7 +291,7 @@
]
}
},
- "summary": "Deleted '5' in the [...]int array of the 'main' function"
+ "summary": "Deleted '5' in the [...]int composite_literal of the 'main' function"
},
{
"span": {
@@ -291,7 +306,7 @@
]
}
},
- "summary": "Deleted '6' in the [...]int array of the 'main' function"
+ "summary": "Deleted '6' in the [...]int composite_literal of the 'main' function"
}
]
},
@@ -314,7 +329,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6a2f0882912e58d2f3e34875a6bb44804d586279..b8316cf1b4504b16bf1ede60ccd875adbc2f737b"
+ "shas": "235fa8a9d47005f230e6db96c1d2bf4d8e935851..2dce176e86c49d2fd4be864e3a388ac25674f9d1"
}
,{
"testCaseDescription": "go-array-with-implicit-length-delete-insert-test",
@@ -334,7 +349,7 @@
]
}
},
- "summary": "Deleted the 'a1' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'a1' var assignment in the main function"
}
]
},
@@ -357,7 +372,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b8316cf1b4504b16bf1ede60ccd875adbc2f737b..555892195608bc7b16f133fe3389a59785aa83bf"
+ "shas": "2dce176e86c49d2fd4be864e3a388ac25674f9d1..b98fb6db21b918f40b3caf936b11bb72c07cb9dd"
}
,{
"testCaseDescription": "go-array-with-implicit-length-teardown-test",
@@ -372,12 +387,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -399,5 +429,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "555892195608bc7b16f133fe3389a59785aa83bf..6e579109cc2a3c535790233b54306a5473f1a55d"
+ "shas": "b98fb6db21b918f40b3caf936b11bb72c07cb9dd..b8e41392436d04ec37de7c7358f5c6f016fc7726"
}]
diff --git a/test/corpus/diff-summaries/go/assignment-statements.json b/test/corpus/diff-summaries/go/assignment-statements.json
index 1260eef3e..da97f7fb8 100644
--- a/test/corpus/diff-summaries/go/assignment-statements.json
+++ b/test/corpus/diff-summaries/go/assignment-statements.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "091bc58290f6343880a29ef209a9d87aa7a3fcc0..545e6cd93c1d697e514d1fdad37a57f0d937a526"
+ "shas": "65295513fb69f053f466c62e25b12d37872a7543..90d5492eca694a1db6462f9037889549357c3854"
}
,{
"testCaseDescription": "go-assignment-statements-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'a' assignment in the main function"
},
{
"span": {
@@ -73,22 +88,7 @@
]
}
},
- "summary": "Added the 'b' var assignment in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 1
- ],
- "end": [
- 5,
- 13
- ]
- }
- },
- "summary": "Added the 'c' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'b, c' assignment in the main function"
},
{
"span": {
@@ -103,7 +103,7 @@
]
}
},
- "summary": "Added the 'd' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'd' assignment in the main function"
},
{
"span": {
@@ -118,7 +118,7 @@
]
}
},
- "summary": "Added the 'e' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'e' assignment in the main function"
}
]
},
@@ -144,7 +144,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "545e6cd93c1d697e514d1fdad37a57f0d937a526..e0bbb0f31468f4684ee8e2777fc8993596caa1f0"
+ "shas": "90d5492eca694a1db6462f9037889549357c3854..98ea82656603de04b6b95f411bdcfd58b63e189e"
}
,{
"testCaseDescription": "go-assignment-statements-replacement-test",
@@ -176,7 +176,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'x' identifier in the x var assignment of the 'main' function"
+ "summary": "Replaced the 'a' identifier with the 'x' identifier in an assignment to x of the 'main' function"
},
{
"span": {
@@ -203,22 +203,34 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'y' identifier in the y var assignment of the 'main' function"
+ "summary": "Replaced the 'b' identifier with the 'y' identifier in an assignment to y, c of the 'main' function"
},
{
"span": {
- "insert": {
- "start": [
- 6,
- 1
- ],
- "end": [
- 6,
- 7
- ]
- }
+ "replace": [
+ {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ },
+ {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ ]
},
- "summary": "Added the 'z' var assignment in the main function of the 'main' module"
+ "summary": "Replaced the 'd' identifier with the 'z' identifier in an assignment to z of the 'main' function"
},
{
"span": {
@@ -233,22 +245,7 @@
]
}
},
- "summary": "Added the 'h' var assignment in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 6,
- 1
- ],
- "end": [
- 6,
- 7
- ]
- }
- },
- "summary": "Deleted the 'd' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'h' assignment in the main function"
},
{
"span": {
@@ -263,7 +260,7 @@
]
}
},
- "summary": "Deleted the 'e' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'e' assignment in the main function"
}
]
},
@@ -292,7 +289,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e0bbb0f31468f4684ee8e2777fc8993596caa1f0..284fe9eeee9487470f4e11d93047de38ef682b7e"
+ "shas": "98ea82656603de04b6b95f411bdcfd58b63e189e..4130e7b48740376e3b3e44d8c622245374813a1f"
}
,{
"testCaseDescription": "go-assignment-statements-delete-replacement-test",
@@ -324,7 +321,7 @@
}
]
},
- "summary": "Replaced the 'x' identifier with the 'a' identifier in the a var assignment of the 'main' function"
+ "summary": "Replaced the 'x' identifier with the 'a' identifier in an assignment to a of the 'main' function"
},
{
"span": {
@@ -351,76 +348,49 @@
}
]
},
- "summary": "Replaced the 'y' identifier with the 'b' identifier in the b var assignment of the 'main' function"
+ "summary": "Replaced the 'y' identifier with the 'b' identifier in an assignment to b, c of the 'main' function"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ },
+ {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 2
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'z' identifier with the 'd' identifier in an assignment to d of the 'main' function"
},
{
"span": {
"insert": {
"start": [
- 6,
+ 7,
1
],
"end": [
- 6,
+ 7,
7
]
}
},
- "summary": "Added the 'd' var assignment in the main function of the 'main' module"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 6,
- 1
- ],
- "end": [
- 6,
- 2
- ]
- },
- {
- "start": [
- 7,
- 1
- ],
- "end": [
- 7,
- 2
- ]
- }
- ]
- },
- "summary": "Replaced the 'z' identifier with the 'e' identifier in the e var assignment of the 'main' function"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 6,
- 6
- ],
- "end": [
- 6,
- 7
- ]
- },
- {
- "start": [
- 7,
- 6
- ],
- "end": [
- 7,
- 7
- ]
- }
- ]
- },
- "summary": "Replaced '3' with '1' in the e var assignment of the 'main' function"
+ "summary": "Added the 'e' assignment in the main function"
},
{
"span": {
@@ -435,7 +405,7 @@
]
}
},
- "summary": "Deleted the 'h' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'h' assignment in the main function"
}
]
},
@@ -464,7 +434,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "284fe9eeee9487470f4e11d93047de38ef682b7e..6ab478bb986f0227f287e5128a038117685d82f0"
+ "shas": "4130e7b48740376e3b3e44d8c622245374813a1f..67ba411108a71a2f98e7bc597e4178dbcfac0031"
}
,{
"testCaseDescription": "go-assignment-statements-delete-insert-test",
@@ -484,7 +454,7 @@
]
}
},
- "summary": "Deleted the 'a' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'a' assignment in the main function"
},
{
"span": {
@@ -499,22 +469,7 @@
]
}
},
- "summary": "Deleted the 'b' var assignment in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 1
- ],
- "end": [
- 5,
- 13
- ]
- }
- },
- "summary": "Deleted the 'c' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'b, c' assignment in the main function"
},
{
"span": {
@@ -529,7 +484,7 @@
]
}
},
- "summary": "Deleted the 'd' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'd' assignment in the main function"
},
{
"span": {
@@ -544,7 +499,7 @@
]
}
},
- "summary": "Deleted the 'e' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'e' assignment in the main function"
}
]
},
@@ -570,7 +525,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6ab478bb986f0227f287e5128a038117685d82f0..6963690336efde9f4763222a83afe4ce714bf5e7"
+ "shas": "67ba411108a71a2f98e7bc597e4178dbcfac0031..36092fdf255e0236862c27135098a4fa4e9dbd75"
}
,{
"testCaseDescription": "go-assignment-statements-teardown-test",
@@ -585,12 +540,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -612,5 +582,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6963690336efde9f4763222a83afe4ce714bf5e7..2d4500613c50791e41a932edd1885da8e9830f8e"
+ "shas": "36092fdf255e0236862c27135098a4fa4e9dbd75..3f2a09bd95dfbff3712c14095a53c1f0a3855648"
}]
diff --git a/test/corpus/diff-summaries/go/call-expressions.json b/test/corpus/diff-summaries/go/call-expressions.json
index 527b44177..c59cddd95 100644
--- a/test/corpus/diff-summaries/go/call-expressions.json
+++ b/test/corpus/diff-summaries/go/call-expressions.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "47074688bbb73b3e4bf4fe48f221e411e5a9dcae..0bed7aaac9a7223bee7e747c7e956609d61b142f"
+ "shas": "d5f8f49ab00e91cf9cf8a71dd94c14b3fa29aad8..0f348f4e761af93c4036be91a81c370254edab79"
}
,{
"testCaseDescription": "go-call-expressions-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'x(b, c)' function call in the main function of the 'main' module"
+ "summary": "Added the 'x(b, c)' function call in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'y(b, c)' function call in the main function of the 'main' module"
+ "summary": "Added the 'y(b, c)' function call in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 'z(b, c)' function call in the main function of the 'main' module"
+ "summary": "Added the 'z(b, c)' function call in the main function"
}
]
},
@@ -113,7 +128,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "0bed7aaac9a7223bee7e747c7e956609d61b142f..aba38b132e19f43e2dbbe7c9f084f7e89348a63f"
+ "shas": "0f348f4e761af93c4036be91a81c370254edab79..8032ef9f0136e422475ec94f40416071beacb1b3"
}
,{
"testCaseDescription": "go-call-expressions-replacement-test",
@@ -133,7 +148,7 @@
]
}
},
- "summary": "Added the 'a(b, c)' function call in the main function of the 'main' module"
+ "summary": "Added the 'a(b, c)' function call in the main function"
},
{
"span": {
@@ -148,7 +163,7 @@
]
}
},
- "summary": "Added the 'b(b, c)' function call in the main function of the 'main' module"
+ "summary": "Added the 'b(b, c)' function call in the main function"
},
{
"span": {
@@ -163,7 +178,7 @@
]
}
},
- "summary": "Added the 'c(b, c)' function call in the main function of the 'main' module"
+ "summary": "Added the 'c(b, c)' function call in the main function"
},
{
"span": {
@@ -178,7 +193,7 @@
]
}
},
- "summary": "Deleted the 'x(b, c)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'x(b, c)' function call in the main function"
},
{
"span": {
@@ -193,7 +208,7 @@
]
}
},
- "summary": "Deleted the 'y(b, c)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'y(b, c)' function call in the main function"
},
{
"span": {
@@ -208,7 +223,7 @@
]
}
},
- "summary": "Deleted the 'z(b, c)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'z(b, c)' function call in the main function"
}
]
},
@@ -235,7 +250,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "aba38b132e19f43e2dbbe7c9f084f7e89348a63f..a75e3fa8a8d7ff7860d1e63172a25e15146f8970"
+ "shas": "8032ef9f0136e422475ec94f40416071beacb1b3..8dda64263242afa2d8deb5d25140852ebfb07b71"
}
,{
"testCaseDescription": "go-call-expressions-delete-replacement-test",
@@ -255,7 +270,7 @@
]
}
},
- "summary": "Added the 'x(b, c)' function call in the main function of the 'main' module"
+ "summary": "Added the 'x(b, c)' function call in the main function"
},
{
"span": {
@@ -270,7 +285,7 @@
]
}
},
- "summary": "Added the 'y(b, c)' function call in the main function of the 'main' module"
+ "summary": "Added the 'y(b, c)' function call in the main function"
},
{
"span": {
@@ -285,7 +300,7 @@
]
}
},
- "summary": "Added the 'z(b, c)' function call in the main function of the 'main' module"
+ "summary": "Added the 'z(b, c)' function call in the main function"
},
{
"span": {
@@ -300,7 +315,7 @@
]
}
},
- "summary": "Deleted the 'a(b, c)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'a(b, c)' function call in the main function"
},
{
"span": {
@@ -315,7 +330,7 @@
]
}
},
- "summary": "Deleted the 'b(b, c)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'b(b, c)' function call in the main function"
},
{
"span": {
@@ -330,7 +345,7 @@
]
}
},
- "summary": "Deleted the 'c(b, c)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'c(b, c)' function call in the main function"
}
]
},
@@ -357,7 +372,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a75e3fa8a8d7ff7860d1e63172a25e15146f8970..a954830b0bda0e385a0a8eb61e6e4a123d2dfb66"
+ "shas": "8dda64263242afa2d8deb5d25140852ebfb07b71..dd71d5503cc5e5b1f7e85ccabd36d64c891e48d2"
}
,{
"testCaseDescription": "go-call-expressions-delete-insert-test",
@@ -377,7 +392,7 @@
]
}
},
- "summary": "Deleted the 'x(b, c)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'x(b, c)' function call in the main function"
},
{
"span": {
@@ -392,7 +407,7 @@
]
}
},
- "summary": "Deleted the 'y(b, c)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'y(b, c)' function call in the main function"
},
{
"span": {
@@ -407,7 +422,7 @@
]
}
},
- "summary": "Deleted the 'z(b, c)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'z(b, c)' function call in the main function"
}
]
},
@@ -432,7 +447,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a954830b0bda0e385a0a8eb61e6e4a123d2dfb66..d5de8ed9734efb140a7bb970951f13a1ca345dad"
+ "shas": "dd71d5503cc5e5b1f7e85ccabd36d64c891e48d2..a9a077abbee74593f4f64c4491602102a47e0f0d"
}
,{
"testCaseDescription": "go-call-expressions-teardown-test",
@@ -447,12 +462,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -474,5 +504,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d5de8ed9734efb140a7bb970951f13a1ca345dad..a5f99e0c9f8b9b96e1f64f8b5fd79ed8c9490ebd"
+ "shas": "a9a077abbee74593f4f64c4491602102a47e0f0d..cbd953ad26bc63e3ddd57f753a0d7bf09ed21706"
}]
diff --git a/test/corpus/diff-summaries/go/case-statements.json b/test/corpus/diff-summaries/go/case-statements.json
index c7deb909e..55a17e1ee 100644
--- a/test/corpus/diff-summaries/go/case-statements.json
+++ b/test/corpus/diff-summaries/go/case-statements.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d294ce5018da872a8921d3401c507217daf06328..c54949d55a43937b2ac33296ac3b5cecb50d6382"
+ "shas": "840ffcc3fb49c5769944cce7b4fc8f444c2b1aed..30e5ee71dd288a98026159bc4762ba813caf1e5a"
}
,{
"testCaseDescription": "go-case-statements-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added a switch statement in the main function of the 'main' module"
+ "summary": "Added a switch statement in the main function"
}
]
},
@@ -81,7 +96,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c54949d55a43937b2ac33296ac3b5cecb50d6382..c215ea9b6a3b10e2eaa8ae424350795e9f093004"
+ "shas": "30e5ee71dd288a98026159bc4762ba813caf1e5a..a7af99836429ee5953956b39612d30c98099952d"
}
,{
"testCaseDescription": "go-case-statements-replacement-test",
@@ -93,15 +108,15 @@
"insert": {
"start": [
4,
- 1
+ 10
],
"end": [
4,
- 26
+ 24
]
}
},
- "summary": "Added the 'foo' case statement in a switch statement of the 'main' function"
+ "summary": "Added the 'case foo' case statement in a switch statement of the 'main' function"
}
]
},
@@ -124,7 +139,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c215ea9b6a3b10e2eaa8ae424350795e9f093004..7d12abcf1f4702639d6e7363776cfdf6598491b7"
+ "shas": "a7af99836429ee5953956b39612d30c98099952d..ce974189409e1cc2547615421f390b953e234699"
}
,{
"testCaseDescription": "go-case-statements-delete-replacement-test",
@@ -136,15 +151,15 @@
"delete": {
"start": [
4,
- 1
+ 10
],
"end": [
4,
- 26
+ 24
]
}
},
- "summary": "Deleted the 'foo' case statement in a switch statement of the 'main' function"
+ "summary": "Deleted the 'case foo' case statement in a switch statement of the 'main' function"
}
]
},
@@ -167,7 +182,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7d12abcf1f4702639d6e7363776cfdf6598491b7..e7a7b4af3503fe63d5a954f7b5576a09d2185778"
+ "shas": "ce974189409e1cc2547615421f390b953e234699..84d84920f7bcdff865c2a05d49e6d3d98e633866"
}
,{
"testCaseDescription": "go-case-statements-delete-insert-test",
@@ -187,7 +202,7 @@
]
}
},
- "summary": "Deleted a switch statement in the main function of the 'main' module"
+ "summary": "Deleted a switch statement in the main function"
}
]
},
@@ -210,7 +225,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e7a7b4af3503fe63d5a954f7b5576a09d2185778..4fc08573a3964379df9d9213e239adc5b9048eb5"
+ "shas": "84d84920f7bcdff865c2a05d49e6d3d98e633866..c455ac8dfc52ad0fcd50455429971b6e5814a066"
}
,{
"testCaseDescription": "go-case-statements-teardown-test",
@@ -225,12 +240,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -252,5 +282,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "4fc08573a3964379df9d9213e239adc5b9048eb5..965eb67a3019ef8aea91e5f5a3975bd6c27ddbd5"
+ "shas": "c455ac8dfc52ad0fcd50455429971b6e5814a066..65bbc171b8f70b289f47abe480d261056b5ea251"
}]
diff --git a/test/corpus/diff-summaries/go/channel-types.json b/test/corpus/diff-summaries/go/channel-types.json
index 2e8a7fa98..158207033 100644
--- a/test/corpus/diff-summaries/go/channel-types.json
+++ b/test/corpus/diff-summaries/go/channel-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ffe628ad363e676d5234caa95a87cf6b7f3626f8..ee8ae407698b4ba69acdd85afb82dcfe2afc2392"
+ "shas": "8ae798e3c9773e3d5b6af35228d06445dd50426f..6fe1a8a05f8eeab5c979450824cdceb0e994abc8"
}
,{
"testCaseDescription": "go-channel-types-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'c1' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'c1' type declaration in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'c2' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'c2' type declaration in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 'c3' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'c3' type declaration in the main function"
}
]
},
@@ -115,7 +130,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ee8ae407698b4ba69acdd85afb82dcfe2afc2392..9c27dde8873170108674ea419a12befe26e5f35a"
+ "shas": "6fe1a8a05f8eeab5c979450824cdceb0e994abc8..61f2e4717656268758d47a3c63c366ab6478f195"
}
,{
"testCaseDescription": "go-channel-types-replacement-test",
@@ -135,7 +150,7 @@
]
}
},
- "summary": "Added the 'c2' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'c2' type declaration in the main function"
},
{
"span": {
@@ -150,7 +165,7 @@
]
}
},
- "summary": "Added the 'c3' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'c3' type declaration in the main function"
},
{
"span": {
@@ -219,7 +234,7 @@
]
}
},
- "summary": "Deleted the 'c2' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'c2' type declaration in the main function"
},
{
"span": {
@@ -234,7 +249,7 @@
]
}
},
- "summary": "Deleted the 'c3' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'c3' type declaration in the main function"
}
]
},
@@ -262,7 +277,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9c27dde8873170108674ea419a12befe26e5f35a..6f3368fcd07690cdf7f7d4d61f8eaa947c9e3f15"
+ "shas": "61f2e4717656268758d47a3c63c366ab6478f195..911fb96ddd154bd39c0c4434674776d5c08202f2"
}
,{
"testCaseDescription": "go-channel-types-delete-replacement-test",
@@ -282,7 +297,7 @@
]
}
},
- "summary": "Added the 'c1' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'c1' type declaration in the main function"
},
{
"span": {
@@ -351,7 +366,7 @@
]
}
},
- "summary": "Deleted the 'c4' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'c4' type declaration in the main function"
}
]
},
@@ -379,7 +394,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6f3368fcd07690cdf7f7d4d61f8eaa947c9e3f15..fd1261f44224fa51c15b3a11b47a0cd38e79a9b7"
+ "shas": "911fb96ddd154bd39c0c4434674776d5c08202f2..d31e3bb2f6b29b37edbb1c325a5511c763a405d1"
}
,{
"testCaseDescription": "go-channel-types-delete-insert-test",
@@ -399,7 +414,7 @@
]
}
},
- "summary": "Deleted the 'c1' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'c1' type declaration in the main function"
},
{
"span": {
@@ -414,7 +429,7 @@
]
}
},
- "summary": "Deleted the 'c2' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'c2' type declaration in the main function"
},
{
"span": {
@@ -429,7 +444,7 @@
]
}
},
- "summary": "Deleted the 'c3' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'c3' type declaration in the main function"
}
]
},
@@ -456,7 +471,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "fd1261f44224fa51c15b3a11b47a0cd38e79a9b7..492604fdcd016b630b1c780e3593d58aeb587a5b"
+ "shas": "d31e3bb2f6b29b37edbb1c325a5511c763a405d1..e9f2625fc7ae3bb80505b2f21de51da17d92d883"
}
,{
"testCaseDescription": "go-channel-types-teardown-test",
@@ -471,12 +486,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -498,5 +528,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "492604fdcd016b630b1c780e3593d58aeb587a5b..cc8aac0f8db0de4e459571ae4c68771e7c442c63"
+ "shas": "e9f2625fc7ae3bb80505b2f21de51da17d92d883..190f44e86419bb122daf395748920e3c5779b66b"
}]
diff --git a/test/corpus/diff-summaries/go/comment.json b/test/corpus/diff-summaries/go/comment.json
index ca78968c1..58b1ad56b 100644
--- a/test/corpus/diff-summaries/go/comment.json
+++ b/test/corpus/diff-summaries/go/comment.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,30 +53,12 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d6bf5b852da48acbbdc8d627de9e645d28d7f38d..72de8c7f39e9b0669a38c1babcdffcff64e96ea5"
+ "shas": "67d576bfc545aeab08b6970a41866b4643831ec5..9c970f2efc403f74275b43a78017615dc8d96d34"
}
,{
"testCaseDescription": "go-comment-insert-test",
"expectedResult": {
- "changes": {
- "comment.go": [
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 21
- ]
- }
- },
- "summary": "Added the '// this is a comment' comment in the main function of the 'main' module"
- }
- ]
- },
+ "changes": {},
"errors": {}
},
"filePaths": [
@@ -81,42 +78,12 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "72de8c7f39e9b0669a38c1babcdffcff64e96ea5..52ce6212c93764a59bdb61da67e20b54d3f288c6"
+ "shas": "9c970f2efc403f74275b43a78017615dc8d96d34..10fa1c97aa81bb87a389d1ead5d52eda2754a14b"
}
,{
"testCaseDescription": "go-comment-replacement-test",
"expectedResult": {
- "changes": {
- "comment.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 21
- ]
- },
- {
- "start": [
- 4,
- 1
- ],
- "end": [
- 6,
- 3
- ]
- }
- ]
- },
- "summary": "Replaced the '// this is a comment' comment with the '/*\nthis is a block comment\n*/' comment in the main function of the 'main' module"
- }
- ]
- },
+ "changes": {},
"errors": {}
},
"filePaths": [
@@ -138,42 +105,12 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "52ce6212c93764a59bdb61da67e20b54d3f288c6..0224d1c4ae63ed9bc69a5b9da5a691cae9c3b34a"
+ "shas": "10fa1c97aa81bb87a389d1ead5d52eda2754a14b..2fa774b3862130654f8cca4f2be3dac35b209fc5"
}
,{
"testCaseDescription": "go-comment-delete-replacement-test",
"expectedResult": {
- "changes": {
- "comment.go": [
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
- 1
- ],
- "end": [
- 6,
- 3
- ]
- },
- {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 21
- ]
- }
- ]
- },
- "summary": "Replaced the '/*\nthis is a block comment\n*/' comment with the '// this is a comment' comment in the main function of the 'main' module"
- }
- ]
- },
+ "changes": {},
"errors": {}
},
"filePaths": [
@@ -195,30 +132,12 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "0224d1c4ae63ed9bc69a5b9da5a691cae9c3b34a..2dd7c846c7d7ee0360f5421181a1c014158ae61e"
+ "shas": "2fa774b3862130654f8cca4f2be3dac35b209fc5..d406d59cc62f4b839107355542037c763747f90b"
}
,{
"testCaseDescription": "go-comment-delete-insert-test",
"expectedResult": {
- "changes": {
- "comment.go": [
- {
- "span": {
- "delete": {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 21
- ]
- }
- },
- "summary": "Deleted the '// this is a comment' comment in the main function of the 'main' module"
- }
- ]
- },
+ "changes": {},
"errors": {}
},
"filePaths": [
@@ -238,7 +157,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "2dd7c846c7d7ee0360f5421181a1c014158ae61e..3e6d5559211855ffca53000e0b49d8c5d1e68bde"
+ "shas": "d406d59cc62f4b839107355542037c763747f90b..e280c452debf7fa9838e27bbda560e056a973742"
}
,{
"testCaseDescription": "go-comment-teardown-test",
@@ -253,12 +172,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -280,5 +214,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "3e6d5559211855ffca53000e0b49d8c5d1e68bde..ab3e3926dc779249680c1d053599892d614e1cbf"
+ "shas": "e280c452debf7fa9838e27bbda560e056a973742..f5a9b8a54a3841db93e420bf8eff96b4d2d6858a"
}]
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 c02a7e8f6..2bfdf549c 100644
--- a/test/corpus/diff-summaries/go/const-declarations-with-types.json
+++ b/test/corpus/diff-summaries/go/const-declarations-with-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "49e6e021a47203dec0d5eef92e0afd35f24628a1..d888fa9002a01cd57957e18377a0498dd5f67341"
+ "shas": "4a6aceb384ae2a8fd0779a62812d50a760f55bda..9b5af2a7e62ee2d129c735f56cc34b089c706020"
}
,{
"testCaseDescription": "go-const-declarations-with-types-insert-test",
@@ -52,13 +67,43 @@
4,
7
],
+ "end": [
+ 4,
+ 11
+ ]
+ }
+ },
+ "summary": "Added the 'zero' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 12
+ ],
+ "end": [
+ 4,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'int' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 18
+ ],
"end": [
4,
19
]
}
},
- "summary": "Added the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Added '0' in the main function"
}
]
},
@@ -81,7 +126,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d888fa9002a01cd57957e18377a0498dd5f67341..04775f661102a38b009cb92e1ac97e69c3b8a279"
+ "shas": "9b5af2a7e62ee2d129c735f56cc34b089c706020..e1177c66dfe74dd4143ee6ac133bdd25f82e5786"
}
,{
"testCaseDescription": "go-const-declarations-with-types-replacement-test",
@@ -113,7 +158,49 @@
}
]
},
- "summary": "Replaced the 'zero' identifier with the 'one' identifier in the one var assignment of the 'main' function"
+ "summary": "Replaced the 'zero' identifier with the 'one' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 12
+ ],
+ "end": [
+ 4,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'two' identifier in the main function"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 4,
+ 12
+ ],
+ "end": [
+ 4,
+ 15
+ ]
+ },
+ {
+ "start": [
+ 4,
+ 16
+ ],
+ "end": [
+ 4,
+ 23
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'int' identifier with the 'uiint64' identifier in the main function"
},
{
"span": {
@@ -140,14 +227,14 @@
}
]
},
- "summary": "Replaced '0' with '1' in the one var assignment of the 'main' function"
+ "summary": "Replaced '0' with '1' in the main function"
},
{
"span": {
"insert": {
"start": [
4,
- 7
+ 29
],
"end": [
4,
@@ -155,7 +242,7 @@
]
}
},
- "summary": "Added the 'two' var assignment in the main function of the 'main' module"
+ "summary": "Added '2' in the main function"
}
]
},
@@ -178,7 +265,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "04775f661102a38b009cb92e1ac97e69c3b8a279..8837603403d627dfaafe8982de7f1b4783ce3fe5"
+ "shas": "e1177c66dfe74dd4143ee6ac133bdd25f82e5786..70e5c6a4cfe3fb36ce3d1ff158e8f303d04d8f95"
}
,{
"testCaseDescription": "go-const-declarations-with-types-delete-replacement-test",
@@ -210,7 +297,49 @@
}
]
},
- "summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero var assignment of the 'main' function"
+ "summary": "Replaced the 'one' identifier with the 'zero' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 12
+ ],
+ "end": [
+ 4,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'two' identifier in the main function"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 4,
+ 16
+ ],
+ "end": [
+ 4,
+ 23
+ ]
+ },
+ {
+ "start": [
+ 4,
+ 12
+ ],
+ "end": [
+ 4,
+ 15
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'uiint64' identifier with the 'int' identifier in the main function"
},
{
"span": {
@@ -237,14 +366,14 @@
}
]
},
- "summary": "Replaced '1' with '0' in the zero var assignment of the 'main' function"
+ "summary": "Replaced '1' with '0' in the main function"
},
{
"span": {
"delete": {
"start": [
4,
- 7
+ 29
],
"end": [
4,
@@ -252,7 +381,7 @@
]
}
},
- "summary": "Deleted the 'two' var assignment in the main function of the 'main' module"
+ "summary": "Deleted '2' in the main function"
}
]
},
@@ -275,7 +404,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8837603403d627dfaafe8982de7f1b4783ce3fe5..687838a4cbf247779e1fa5a133b868839b4d6f8c"
+ "shas": "70e5c6a4cfe3fb36ce3d1ff158e8f303d04d8f95..df53cc08219f7164eb848225b84a7baa8f519650"
}
,{
"testCaseDescription": "go-const-declarations-with-types-delete-insert-test",
@@ -289,13 +418,43 @@
4,
7
],
+ "end": [
+ 4,
+ 11
+ ]
+ }
+ },
+ "summary": "Deleted the 'zero' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 12
+ ],
+ "end": [
+ 4,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 18
+ ],
"end": [
4,
19
]
}
},
- "summary": "Deleted the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Deleted '0' in the main function"
}
]
},
@@ -318,7 +477,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "687838a4cbf247779e1fa5a133b868839b4d6f8c..67348ad5cb4f13aa0f0d2b14b092f9747b950b0f"
+ "shas": "df53cc08219f7164eb848225b84a7baa8f519650..411866d01813ed979fa88a20ba91c74073c361cb"
}
,{
"testCaseDescription": "go-const-declarations-with-types-teardown-test",
@@ -333,12 +492,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -360,5 +534,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "67348ad5cb4f13aa0f0d2b14b092f9747b950b0f..d7c7c21bb12a3b1d9bc3d7ac212a3bdada677d71"
+ "shas": "411866d01813ed979fa88a20ba91c74073c361cb..9c509bdfabb537255c810cd09cf45b53bf65628f"
}]
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 3bcd2f60b..9972ef5ac 100644
--- a/test/corpus/diff-summaries/go/const-declarations-without-types.json
+++ b/test/corpus/diff-summaries/go/const-declarations-without-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "802da3fcac3bb5bd8d87025c78e2dd27694ea5c4..ec2a7031fea2ff0233a9e1c9fe24a97d924abfea"
+ "shas": "bda742d270e92cc83a8a8f229714661cfae58fee..8fae5b68a9e2dc9d3f96f39c86521f932addd607"
}
,{
"testCaseDescription": "go-const-declarations-without-types-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'zero' var assignment in the main function"
}
]
},
@@ -81,7 +96,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ec2a7031fea2ff0233a9e1c9fe24a97d924abfea..4214dd04363c5d7668acb7f4468a4cdb8da3a931"
+ "shas": "8fae5b68a9e2dc9d3f96f39c86521f932addd607..136dc284d185b35d4482cd64e0c82e1ae86df6d5"
}
,{
"testCaseDescription": "go-const-declarations-without-types-replacement-test",
@@ -113,7 +128,22 @@
}
]
},
- "summary": "Replaced the 'zero' identifier with the 'one' identifier in the one var assignment of the 'main' function"
+ "summary": "Replaced the 'zero' identifier with the 'one' identifier in the one, two var assignment of the 'main' function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 12
+ ],
+ "end": [
+ 4,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'two' identifier in the one, two var assignment of the 'main' function"
},
{
"span": {
@@ -140,14 +170,14 @@
}
]
},
- "summary": "Replaced '0' with '1' in the one var assignment of the 'main' function"
+ "summary": "Replaced '0' with '1' in the one, two var assignment of the 'main' function"
},
{
"span": {
"insert": {
"start": [
4,
- 7
+ 21
],
"end": [
4,
@@ -155,7 +185,7 @@
]
}
},
- "summary": "Added the 'two' var assignment in the main function of the 'main' module"
+ "summary": "Added '2' in the one, two var assignment of the 'main' function"
}
]
},
@@ -178,7 +208,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "4214dd04363c5d7668acb7f4468a4cdb8da3a931..4ea74b4fbd9a5a19f10019dcd75e772aad148469"
+ "shas": "136dc284d185b35d4482cd64e0c82e1ae86df6d5..a5bc508cdc3816266f5896654a06d90c8372a929"
}
,{
"testCaseDescription": "go-const-declarations-without-types-delete-replacement-test",
@@ -212,6 +242,21 @@
},
"summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero var assignment of the 'main' function"
},
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 12
+ ],
+ "end": [
+ 4,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'two' identifier in the zero var assignment of the 'main' function"
+ },
{
"span": {
"replace": [
@@ -244,7 +289,7 @@
"delete": {
"start": [
4,
- 7
+ 21
],
"end": [
4,
@@ -252,7 +297,7 @@
]
}
},
- "summary": "Deleted the 'two' var assignment in the main function of the 'main' module"
+ "summary": "Deleted '2' in the zero var assignment of the 'main' function"
}
]
},
@@ -275,7 +320,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "4ea74b4fbd9a5a19f10019dcd75e772aad148469..ad9ba646f6304dddedc688f25eb07527ada8874a"
+ "shas": "a5bc508cdc3816266f5896654a06d90c8372a929..eeec9538fdf788ff7220f7c45e18723c8f8c6213"
}
,{
"testCaseDescription": "go-const-declarations-without-types-delete-insert-test",
@@ -295,7 +340,7 @@
]
}
},
- "summary": "Deleted the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'zero' var assignment in the main function"
}
]
},
@@ -318,7 +363,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ad9ba646f6304dddedc688f25eb07527ada8874a..cc7080fad53918620542bcf3106f75416db8009c"
+ "shas": "eeec9538fdf788ff7220f7c45e18723c8f8c6213..cb36960674fd5af8ce3bb29a4050ad30c517af4a"
}
,{
"testCaseDescription": "go-const-declarations-without-types-teardown-test",
@@ -333,12 +378,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -360,5 +420,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "cc7080fad53918620542bcf3106f75416db8009c..49e6e021a47203dec0d5eef92e0afd35f24628a1"
+ "shas": "cb36960674fd5af8ce3bb29a4050ad30c517af4a..4a6aceb384ae2a8fd0779a62812d50a760f55bda"
}]
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 31b18f41b..d0f0699bc 100644
--- a/test/corpus/diff-summaries/go/const-with-implicit-values.json
+++ b/test/corpus/diff-summaries/go/const-with-implicit-values.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "cbaa77e08635ce41d412574590df4152cae3e4bc..e0c8f19fd1c161ea882f3f342c32cffec193ec12"
+ "shas": "8b23ffed2230fe0c2e75c1a02c179c9ff1726d8f..937443c336d969595e6a83ebc8db77307b5961da"
}
,{
"testCaseDescription": "go-const-with-implicit-values-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'zero' var assignment in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'one' identifier in the main function of the 'main' module"
+ "summary": "Added the 'one' identifier in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 'two' identifier in the main function of the 'main' module"
+ "summary": "Added the 'two' identifier in the main function"
}
]
},
@@ -115,7 +130,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e0c8f19fd1c161ea882f3f342c32cffec193ec12..cdd8a3bc77b30595aa011aa0c1b0de5421c7ad7f"
+ "shas": "937443c336d969595e6a83ebc8db77307b5961da..389c40207cfccd6a33e8ade86a25334277f5c378"
}
,{
"testCaseDescription": "go-const-with-implicit-values-replacement-test",
@@ -174,7 +189,7 @@
}
]
},
- "summary": "Replaced the 'one' identifier with the 'b' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'one' identifier with the 'b' identifier in the main function"
},
{
"span": {
@@ -201,7 +216,7 @@
}
]
},
- "summary": "Replaced the 'two' identifier with the 'c' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'two' identifier with the 'c' identifier in the main function"
}
]
},
@@ -229,7 +244,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "cdd8a3bc77b30595aa011aa0c1b0de5421c7ad7f..6f35b88ea479e8069a61e7cb6615e8932d6898de"
+ "shas": "389c40207cfccd6a33e8ade86a25334277f5c378..efbb02340a4f156d3ca28e917ddb684999f88c29"
}
,{
"testCaseDescription": "go-const-with-implicit-values-delete-replacement-test",
@@ -288,7 +303,7 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'one' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'b' identifier with the 'one' identifier in the main function"
},
{
"span": {
@@ -315,7 +330,7 @@
}
]
},
- "summary": "Replaced the 'c' identifier with the 'two' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'c' identifier with the 'two' identifier in the main function"
}
]
},
@@ -343,7 +358,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6f35b88ea479e8069a61e7cb6615e8932d6898de..8956f659859ecfc3c8399d8d7b60825aeee2aebf"
+ "shas": "efbb02340a4f156d3ca28e917ddb684999f88c29..eec730b7debfaa8297c9b4563171986277737960"
}
,{
"testCaseDescription": "go-const-with-implicit-values-delete-insert-test",
@@ -363,7 +378,7 @@
]
}
},
- "summary": "Deleted the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'zero' var assignment in the main function"
},
{
"span": {
@@ -378,7 +393,7 @@
]
}
},
- "summary": "Deleted the 'one' identifier in the main function of the 'main' module"
+ "summary": "Deleted the 'one' identifier in the main function"
},
{
"span": {
@@ -393,7 +408,7 @@
]
}
},
- "summary": "Deleted the 'two' identifier in the main function of the 'main' module"
+ "summary": "Deleted the 'two' identifier in the main function"
}
]
},
@@ -420,7 +435,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8956f659859ecfc3c8399d8d7b60825aeee2aebf..55a0deb4c32a514960cfc33bae65b4c42e5c3a11"
+ "shas": "eec730b7debfaa8297c9b4563171986277737960..4e2c650c7a3af1c7b5e5a22da3548d002c9ad050"
}
,{
"testCaseDescription": "go-const-with-implicit-values-teardown-test",
@@ -435,12 +450,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -462,5 +492,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "55a0deb4c32a514960cfc33bae65b4c42e5c3a11..e18c5b5c1ca8b1a73b3c2e745671fc99a77f14af"
+ "shas": "4e2c650c7a3af1c7b5e5a22da3548d002c9ad050..024afce27e9882ceae4b057bb8bfb8586761a13f"
}]
diff --git a/test/corpus/diff-summaries/go/constructors.json b/test/corpus/diff-summaries/go/constructors.json
index 7ca12c941..849c35184 100644
--- a/test/corpus/diff-summaries/go/constructors.json
+++ b/test/corpus/diff-summaries/go/constructors.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e18c5b5c1ca8b1a73b3c2e745671fc99a77f14af..25fba0aed3ea4c1773ec3549eaff40d913c079d1"
+ "shas": "024afce27e9882ceae4b057bb8bfb8586761a13f..6fc6c8edcc929af03c8663dc5e5aa3ee5370202c"
}
,{
"testCaseDescription": "go-constructors-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'make(chan<- int)' function call in the main function of the 'main' module"
+ "summary": "Added the 'make(chan<- int)' function call in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'make(chan<- int, …)' function call in the main function of the 'main' module"
+ "summary": "Added the 'make(chan<- int, …)' function call in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 'make(chan<- int, 5, 10)' function call in the main function of the 'main' module"
+ "summary": "Added the 'make(chan<- int, 5, 10)' function call in the main function"
},
{
"span": {
@@ -103,7 +118,7 @@
]
}
},
- "summary": "Added the 'new(…)' function call in the main function of the 'main' module"
+ "summary": "Added the 'new(…)' function call in the main function"
}
]
},
@@ -129,7 +144,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "25fba0aed3ea4c1773ec3549eaff40d913c079d1..e63a03ba5fd522be40676c7ab9df3fa580a42ce1"
+ "shas": "6fc6c8edcc929af03c8663dc5e5aa3ee5370202c..e4b0010eb1c1c21136301481d464e9c4b3c114ae"
}
,{
"testCaseDescription": "go-constructors-replacement-test",
@@ -352,7 +367,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e63a03ba5fd522be40676c7ab9df3fa580a42ce1..663d1012955d9772510ea5a37c0e4875dca5ae3b"
+ "shas": "e4b0010eb1c1c21136301481d464e9c4b3c114ae..56b8228e835ad78277d22d4148192e2ad4111abd"
}
,{
"testCaseDescription": "go-constructors-delete-replacement-test",
@@ -575,7 +590,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "663d1012955d9772510ea5a37c0e4875dca5ae3b..a87fbe18288708a89f31aea5f2dfbe4469bd6440"
+ "shas": "56b8228e835ad78277d22d4148192e2ad4111abd..ace430b5760091e3c1bb339eb0452bc93a155e10"
}
,{
"testCaseDescription": "go-constructors-delete-insert-test",
@@ -595,7 +610,7 @@
]
}
},
- "summary": "Deleted the 'make(chan<- int)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'make(chan<- int)' function call in the main function"
},
{
"span": {
@@ -610,7 +625,7 @@
]
}
},
- "summary": "Deleted the 'make(chan<- int, …)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'make(chan<- int, …)' function call in the main function"
},
{
"span": {
@@ -625,7 +640,7 @@
]
}
},
- "summary": "Deleted the 'make(chan<- int, 5, 10)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'make(chan<- int, 5, 10)' function call in the main function"
},
{
"span": {
@@ -640,7 +655,7 @@
]
}
},
- "summary": "Deleted the 'new(…)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'new(…)' function call in the main function"
}
]
},
@@ -666,7 +681,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a87fbe18288708a89f31aea5f2dfbe4469bd6440..234571e05897ca34177bb1df91bb9beee6be2258"
+ "shas": "ace430b5760091e3c1bb339eb0452bc93a155e10..a5327fc1a6f44c26f33075bb2f294b406574c8a3"
}
,{
"testCaseDescription": "go-constructors-teardown-test",
@@ -681,12 +696,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -708,5 +738,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "234571e05897ca34177bb1df91bb9beee6be2258..92abc0a7c86e4fde9374babdb2efcd398d27f6ac"
+ "shas": "a5327fc1a6f44c26f33075bb2f294b406574c8a3..eca7c6083f4f3169ebc3bf726c3d936818a2d174"
}]
diff --git a/test/corpus/diff-summaries/go/float-literals.json b/test/corpus/diff-summaries/go/float-literals.json
index ddf1a3d99..b8741d595 100644
--- a/test/corpus/diff-summaries/go/float-literals.json
+++ b/test/corpus/diff-summaries/go/float-literals.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "bd47547e797a6e76a34e259077fc32181d6667f5..f5e354dad5a3fbf87368c8d94c2a5f3afe01144b"
+ "shas": "6ea06aa1e8431651d63087d1f623f409947a25f1..a03d106f4668e2d39bf52c3e278b68cf682165b1"
}
,{
"testCaseDescription": "go-float-literals-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'f1' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'f1' assignment in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'f2' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'f2' assignment in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 'f3' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'f3' assignment in the main function"
},
{
"span": {
@@ -103,7 +118,7 @@
]
}
},
- "summary": "Added the 'f4' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'f4' assignment in the main function"
},
{
"span": {
@@ -118,7 +133,7 @@
]
}
},
- "summary": "Added the 'f5' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'f5' assignment in the main function"
}
]
},
@@ -145,7 +160,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "f5e354dad5a3fbf87368c8d94c2a5f3afe01144b..6bffa6e449c92bd384ef85d90fd502ae13553a94"
+ "shas": "a03d106f4668e2d39bf52c3e278b68cf682165b1..841ab7a1e0173f62bcb428551152d9d47f123025"
}
,{
"testCaseDescription": "go-float-literals-replacement-test",
@@ -154,138 +169,153 @@
"float-literals.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 4,
- 6
- ],
- "end": [
- 4,
- 9
- ]
- },
- {
- "start": [
- 4,
- 6
- ],
- "end": [
- 4,
- 9
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 9
+ ]
+ }
},
- "summary": "Replaced the '1.5' float with the '2.6' float in the f1 var assignment of the 'main' function"
+ "summary": "Added the 'f1' assignment in the main function"
},
{
"span": {
- "replace": [
- {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 13
- ]
- },
- {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 13
+ ]
+ }
},
- "summary": "Replaced the '1.5e100' float with the '2.6e211' float in the f2 var assignment of the 'main' function"
+ "summary": "Added the 'f2' assignment in the main function"
},
{
"span": {
- "replace": [
- {
- "start": [
- 6,
- 6
- ],
- "end": [
- 6,
- 13
- ]
- },
- {
- "start": [
- 6,
- 6
- ],
- "end": [
- 6,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 13
+ ]
+ }
},
- "summary": "Replaced the '1.5e+50' float with the '2.6e+60' float in the f3 var assignment of the 'main' function"
+ "summary": "Added the 'f3' assignment in the main function"
},
{
"span": {
- "replace": [
- {
- "start": [
- 7,
- 6
- ],
- "end": [
- 7,
- 12
- ]
- },
- {
- "start": [
- 7,
- 6
- ],
- "end": [
- 7,
- 12
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 12
+ ]
+ }
},
- "summary": "Replaced the '1.5e-5' float with the '2.6e-7' float in the f4 var assignment of the 'main' function"
+ "summary": "Added the 'f4' assignment in the main function"
},
{
"span": {
- "replace": [
- {
- "start": [
- 8,
- 6
- ],
- "end": [
- 8,
- 12
- ]
- },
- {
- "start": [
- 8,
- 6
- ],
- "end": [
- 8,
- 12
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 8,
+ 1
+ ],
+ "end": [
+ 8,
+ 12
+ ]
+ }
},
- "summary": "Replaced the '.5e-50' float with the '.6e-60' float in the f5 var assignment of the 'main' function"
+ "summary": "Added the 'f5' assignment in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'f1' assignment in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'f2' assignment in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'f3' assignment in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the 'f4' assignment in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 1
+ ],
+ "end": [
+ 8,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the 'f5' assignment in the main function"
}
]
},
@@ -316,7 +346,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6bffa6e449c92bd384ef85d90fd502ae13553a94..be9a2fd6304558d0123d42b545eb6de27b3d7e58"
+ "shas": "841ab7a1e0173f62bcb428551152d9d47f123025..5e8653295137112c6645a93a98308e0c690247b7"
}
,{
"testCaseDescription": "go-float-literals-delete-replacement-test",
@@ -325,138 +355,153 @@
"float-literals.go": [
{
"span": {
- "replace": [
- {
- "start": [
- 4,
- 6
- ],
- "end": [
- 4,
- 9
- ]
- },
- {
- "start": [
- 4,
- 6
- ],
- "end": [
- 4,
- 9
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 9
+ ]
+ }
},
- "summary": "Replaced the '2.6' float with the '1.5' float in the f1 var assignment of the 'main' function"
+ "summary": "Added the 'f1' assignment in the main function"
},
{
"span": {
- "replace": [
- {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 13
- ]
- },
- {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 13
+ ]
+ }
},
- "summary": "Replaced the '2.6e211' float with the '1.5e100' float in the f2 var assignment of the 'main' function"
+ "summary": "Added the 'f2' assignment in the main function"
},
{
"span": {
- "replace": [
- {
- "start": [
- 6,
- 6
- ],
- "end": [
- 6,
- 13
- ]
- },
- {
- "start": [
- 6,
- 6
- ],
- "end": [
- 6,
- 13
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 13
+ ]
+ }
},
- "summary": "Replaced the '2.6e+60' float with the '1.5e+50' float in the f3 var assignment of the 'main' function"
+ "summary": "Added the 'f3' assignment in the main function"
},
{
"span": {
- "replace": [
- {
- "start": [
- 7,
- 6
- ],
- "end": [
- 7,
- 12
- ]
- },
- {
- "start": [
- 7,
- 6
- ],
- "end": [
- 7,
- 12
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 12
+ ]
+ }
},
- "summary": "Replaced the '2.6e-7' float with the '1.5e-5' float in the f4 var assignment of the 'main' function"
+ "summary": "Added the 'f4' assignment in the main function"
},
{
"span": {
- "replace": [
- {
- "start": [
- 8,
- 6
- ],
- "end": [
- 8,
- 12
- ]
- },
- {
- "start": [
- 8,
- 6
- ],
- "end": [
- 8,
- 12
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 8,
+ 1
+ ],
+ "end": [
+ 8,
+ 12
+ ]
+ }
},
- "summary": "Replaced the '.6e-60' float with the '.5e-50' float in the f5 var assignment of the 'main' function"
+ "summary": "Added the 'f5' assignment in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'f1' assignment in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'f2' assignment in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'f3' assignment in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 1
+ ],
+ "end": [
+ 7,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the 'f4' assignment in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 1
+ ],
+ "end": [
+ 8,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the 'f5' assignment in the main function"
}
]
},
@@ -487,7 +532,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "be9a2fd6304558d0123d42b545eb6de27b3d7e58..eba46660d9fd1d6bcb4320bbcabd63ef2f97de45"
+ "shas": "5e8653295137112c6645a93a98308e0c690247b7..371f187f2f1bf7fb9a1feff41ea8d1d6c4d3e25e"
}
,{
"testCaseDescription": "go-float-literals-delete-insert-test",
@@ -507,7 +552,7 @@
]
}
},
- "summary": "Deleted the 'f1' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'f1' assignment in the main function"
},
{
"span": {
@@ -522,7 +567,7 @@
]
}
},
- "summary": "Deleted the 'f2' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'f2' assignment in the main function"
},
{
"span": {
@@ -537,7 +582,7 @@
]
}
},
- "summary": "Deleted the 'f3' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'f3' assignment in the main function"
},
{
"span": {
@@ -552,7 +597,7 @@
]
}
},
- "summary": "Deleted the 'f4' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'f4' assignment in the main function"
},
{
"span": {
@@ -567,7 +612,7 @@
]
}
},
- "summary": "Deleted the 'f5' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'f5' assignment in the main function"
}
]
},
@@ -594,7 +639,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "eba46660d9fd1d6bcb4320bbcabd63ef2f97de45..bcccf71a9ce250474dd60b0f6d2b6361c4e83b03"
+ "shas": "371f187f2f1bf7fb9a1feff41ea8d1d6c4d3e25e..e1f25ce6d6735b3b0590d3cf21f59bb32675ff2d"
}
,{
"testCaseDescription": "go-float-literals-teardown-test",
@@ -609,12 +654,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -636,5 +696,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "bcccf71a9ce250474dd60b0f6d2b6361c4e83b03..39b5a7d4eaa477c3d1636e32ab2c5cf5c930372a"
+ "shas": "e1f25ce6d6735b3b0590d3cf21f59bb32675ff2d..663f0278d8c41aca54ae0d1849efc76213f9ba1f"
}]
diff --git a/test/corpus/diff-summaries/go/for-statements.json b/test/corpus/diff-summaries/go/for-statements.json
index f0e43941a..e4ce4dbaf 100644
--- a/test/corpus/diff-summaries/go/for-statements.json
+++ b/test/corpus/diff-summaries/go/for-statements.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a759987355f2393c92a9df39d4c9e56a2ea2ce19..96a05e960540a57f232ce834347a05b414d55d05"
+ "shas": "030876029c6aa56a60b06740ec65bec788ad8715..e273179f5e9abd6bc426d0dabf1d847d9fc3e4f6"
}
,{
"testCaseDescription": "go-for-statements-insert-test",
@@ -49,16 +64,31 @@
"span": {
"insert": {
"start": [
- 4,
- 2
+ 5,
+ 1
],
"end": [
- 7,
- 2
+ 5,
+ 4
]
}
},
- "summary": "Added the 'for {\na()\ngoto loop\n}' for statement in the main function of the 'main' module"
+ "summary": "Added the 'a()' function call in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 6
+ ],
+ "end": [
+ 6,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'loop' identifier in the main function"
},
{
"span": {
@@ -73,7 +103,7 @@
]
}
},
- "summary": "Added the 'i := 0; i < 5; i++' for statement in the main function of the 'main' module"
+ "summary": "Added the 'i := 0; i < 5; i++' for statement in the main function"
},
{
"span": {
@@ -88,7 +118,7 @@
]
}
},
- "summary": "Added the 'i < 10; i++' for statement in the main function of the 'main' module"
+ "summary": "Added the 'i < 10; i++' for statement in the main function"
},
{
"span": {
@@ -103,7 +133,7 @@
]
}
},
- "summary": "Added the 'for ;; {\na()\ncontinue\n}' for statement in the main function of the 'main' module"
+ "summary": "Added the 'for ;; {\na()\ncontinue\n}' for statement in the main function"
},
{
"span": {
@@ -118,7 +148,7 @@
]
}
},
- "summary": "Added the 'x := range y' for statement in the main function of the 'main' module"
+ "summary": "Added the 'x := range y' for statement in the main function"
}
]
},
@@ -160,13 +190,28 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "96a05e960540a57f232ce834347a05b414d55d05..51b3d18d617cd963d917fb4792134e63ceb460df"
+ "shas": "e273179f5e9abd6bc426d0dabf1d847d9fc3e4f6..f25b62b1979ac923c37947e26b12ab7b07772a65"
}
,{
"testCaseDescription": "go-for-statements-replacement-test",
"expectedResult": {
"changes": {
"for-statements.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 2
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'for ;; {\na()\ngoto loop\n}' for statement in the main function"
+ },
{
"span": {
"insert": {
@@ -180,7 +225,7 @@
]
}
},
- "summary": "Added the 'x := range y' for statement in the main function of the 'main' module"
+ "summary": "Added the 'x := range y' for statement in the main function"
},
{
"span": {
@@ -195,7 +240,7 @@
]
}
},
- "summary": "Added the 'for ;; {\na()\ncontinue loop2\n}' for statement in the main function of the 'main' module"
+ "summary": "Added the 'for ;; {\na()\ncontinue loop2\n}' for statement in the main function"
},
{
"span": {
@@ -210,22 +255,52 @@
]
}
},
- "summary": "Added the 'i < 10; i++' for statement in the main function of the 'main' module"
+ "summary": "Added the 'i < 10; i++' for statement in the main function"
},
{
"span": {
"insert": {
"start": [
- 20,
- 1
+ 21,
+ 3
],
"end": [
- 23,
- 2
+ 21,
+ 4
]
}
},
- "summary": "Added the 'for {\na(x)\nbreak\n}' for statement in the main function of the 'main' module"
+ "summary": "Added the 'x' identifier in the a(x) function call of the 'main' function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 22,
+ 1
+ ],
+ "end": [
+ 22,
+ 6
+ ]
+ }
+ },
+ "summary": "Added a break statement in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 6
+ ],
+ "end": [
+ 6,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted the 'loop' identifier in the main function"
},
{
"span": {
@@ -240,7 +315,7 @@
]
}
},
- "summary": "Deleted the 'i := 0; i < 5; i++' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'i := 0; i < 5; i++' for statement in the main function"
},
{
"span": {
@@ -255,7 +330,7 @@
]
}
},
- "summary": "Deleted the 'i < 10; i++' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'i < 10; i++' for statement in the main function"
},
{
"span": {
@@ -270,7 +345,7 @@
]
}
},
- "summary": "Deleted the 'for ;; {\na()\ncontinue\n}' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'for ;; {\na()\ncontinue\n}' for statement in the main function"
},
{
"span": {
@@ -285,7 +360,7 @@
]
}
},
- "summary": "Deleted the 'x := range y' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'x := range y' for statement in the main function"
}
]
},
@@ -330,13 +405,43 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "51b3d18d617cd963d917fb4792134e63ceb460df..bc8c77df5715b792acde0ee8f5348762365c458e"
+ "shas": "f25b62b1979ac923c37947e26b12ab7b07772a65..1d87bb5117646fb05a6eb77fab4add841c79e49c"
}
,{
"testCaseDescription": "go-for-statements-delete-replacement-test",
"expectedResult": {
"changes": {
"for-statements.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'a()' function call in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 6
+ ],
+ "end": [
+ 6,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'loop' identifier in the main function"
+ },
{
"span": {
"insert": {
@@ -350,7 +455,7 @@
]
}
},
- "summary": "Added the 'i := 0; i < 5; i++' for statement in the main function of the 'main' module"
+ "summary": "Added the 'i := 0; i < 5; i++' for statement in the main function"
},
{
"span": {
@@ -365,22 +470,34 @@
]
}
},
- "summary": "Added the 'i < 10; i++' for statement in the main function of the 'main' module"
+ "summary": "Added the 'i < 10; i++' for statement in the main function"
},
{
"span": {
- "insert": {
- "start": [
- 16,
- 1
- ],
- "end": [
- 19,
- 2
- ]
- }
+ "replace": [
+ {
+ "start": [
+ 4,
+ 2
+ ],
+ "end": [
+ 7,
+ 2
+ ]
+ },
+ {
+ "start": [
+ 16,
+ 1
+ ],
+ "end": [
+ 19,
+ 2
+ ]
+ }
+ ]
},
- "summary": "Added the 'for ;; {\na()\ncontinue\n}' for statement in the main function of the 'main' module"
+ "summary": "Replaced the 'for ;; {\na()\ngoto loop\n}' for statement with the 'for ;; {\na()\ncontinue\n}' for statement in the main function"
},
{
"span": {
@@ -410,7 +527,7 @@
]
}
},
- "summary": "Deleted the 'loop' identifier in the main function of the 'main' module"
+ "summary": "Deleted the 'loop' identifier in the main function"
},
{
"span": {
@@ -425,7 +542,7 @@
]
}
},
- "summary": "Deleted the 'for ;; {\na()\ncontinue loop2\n}' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'for ;; {\na()\ncontinue loop2\n}' for statement in the main function"
},
{
"span": {
@@ -440,22 +557,37 @@
]
}
},
- "summary": "Deleted the 'i < 10; i++' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'i < 10; i++' for statement in the main function"
},
{
"span": {
"delete": {
"start": [
- 20,
+ 21,
1
],
"end": [
- 23,
- 2
+ 21,
+ 5
]
}
},
- "summary": "Deleted the 'for {\na(x)\nbreak\n}' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'a(x)' function call in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 22,
+ 1
+ ],
+ "end": [
+ 22,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted a break statement in the main function"
}
]
},
@@ -500,7 +632,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "bc8c77df5715b792acde0ee8f5348762365c458e..8053ecd74ec3e0c07b9fea654f0b8fcce78a3d76"
+ "shas": "1d87bb5117646fb05a6eb77fab4add841c79e49c..1743b5d6f9c95bb0d7dbec59c2e254d7d444ca0f"
}
,{
"testCaseDescription": "go-for-statements-delete-insert-test",
@@ -511,16 +643,31 @@
"span": {
"delete": {
"start": [
- 4,
- 2
+ 5,
+ 1
],
"end": [
- 7,
- 2
+ 5,
+ 4
]
}
},
- "summary": "Deleted the 'for {\na()\ngoto loop\n}' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'a()' function call in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 6
+ ],
+ "end": [
+ 6,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted the 'loop' identifier in the main function"
},
{
"span": {
@@ -535,7 +682,7 @@
]
}
},
- "summary": "Deleted the 'i := 0; i < 5; i++' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'i := 0; i < 5; i++' for statement in the main function"
},
{
"span": {
@@ -550,7 +697,7 @@
]
}
},
- "summary": "Deleted the 'i < 10; i++' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'i < 10; i++' for statement in the main function"
},
{
"span": {
@@ -565,7 +712,7 @@
]
}
},
- "summary": "Deleted the 'for ;; {\na()\ncontinue\n}' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'for ;; {\na()\ncontinue\n}' for statement in the main function"
},
{
"span": {
@@ -580,7 +727,7 @@
]
}
},
- "summary": "Deleted the 'x := range y' for statement in the main function of the 'main' module"
+ "summary": "Deleted the 'x := range y' for statement in the main function"
}
]
},
@@ -622,7 +769,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8053ecd74ec3e0c07b9fea654f0b8fcce78a3d76..109ecfd74440e6d35d565ab30dc4fa34a656edbd"
+ "shas": "1743b5d6f9c95bb0d7dbec59c2e254d7d444ca0f..59eb24ea939ad8ac2cf5e8e16edce93aac3981fd"
}
,{
"testCaseDescription": "go-for-statements-teardown-test",
@@ -637,12 +784,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -664,5 +826,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "109ecfd74440e6d35d565ab30dc4fa34a656edbd..090bcfe2072c5d36d06f9f588c308abeb046e46e"
+ "shas": "59eb24ea939ad8ac2cf5e8e16edce93aac3981fd..b9e8cbc963d70681826124d682474977bcef4d33"
}]
diff --git a/test/corpus/diff-summaries/go/function-declarations.json b/test/corpus/diff-summaries/go/function-declarations.json
index c6d28e88e..fd591d312 100644
--- a/test/corpus/diff-summaries/go/function-declarations.json
+++ b/test/corpus/diff-summaries/go/function-declarations.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "090bcfe2072c5d36d06f9f588c308abeb046e46e..4c821ecfcd1dffc01f8b59326d656fa810c27da1"
+ "shas": "b9e8cbc963d70681826124d682474977bcef4d33..75b2b30297a1bb14866f352c5291cae0ad1711b6"
}
,{
"testCaseDescription": "go-function-declarations-insert-test",
@@ -54,8 +69,8 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
},
{
@@ -64,13 +79,13 @@
1
],
"end": [
- 8,
+ 9,
1
]
}
]
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Replaced the 'main' module with 'package main\n\nfunc main() {\nfunc f1() {}\nfunc f2(a int, b, c, d string) int {}\nfunc f2() (int, error) {}\nfunc f2() (result int, err error) {}\n}\n' at line 1, column 1 - line 9, column 1"
}
]
},
@@ -96,7 +111,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "4c821ecfcd1dffc01f8b59326d656fa810c27da1..bcd66229a828820e1dc6df15bdc2e17348f1adcb"
+ "shas": "75b2b30297a1bb14866f352c5291cae0ad1711b6..aced7850a95b463c3083658d0a6b2a9e25021b74"
}
,{
"testCaseDescription": "go-function-declarations-replacement-test",
@@ -155,7 +170,7 @@
}
]
},
- "summary": "Replaced the 'f2' identifier with the 'fb' identifier in the fb function of the 'main' module"
+ "summary": "Replaced the 'f2' identifier with the 'fb' identifier in the fb function"
},
{
"span": {
@@ -182,7 +197,7 @@
}
]
},
- "summary": "Replaced the 'f2' identifier with the 'fc' identifier in the fc function of the 'main' module"
+ "summary": "Replaced the 'f2' identifier with the 'fc' identifier in the fc function"
},
{
"span": {
@@ -209,7 +224,7 @@
}
]
},
- "summary": "Replaced the 'f2' identifier with the 'fd' identifier in the fd function of the 'main' module"
+ "summary": "Replaced the 'f2' identifier with the 'fd' identifier in the fd function"
}
]
},
@@ -238,7 +253,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "bcd66229a828820e1dc6df15bdc2e17348f1adcb..25682bee4a82b03d9d7f9ab96c28428ad50270dc"
+ "shas": "aced7850a95b463c3083658d0a6b2a9e25021b74..d0160ccee51c30218f5ca3f776ca8c21cf6ccfd2"
}
,{
"testCaseDescription": "go-function-declarations-delete-replacement-test",
@@ -297,7 +312,7 @@
}
]
},
- "summary": "Replaced the 'fb' identifier with the 'f2' identifier in the f2 function of the 'main' module"
+ "summary": "Replaced the 'fb' identifier with the 'f2' identifier in the f2 function"
},
{
"span": {
@@ -324,7 +339,7 @@
}
]
},
- "summary": "Replaced the 'fc' identifier with the 'f2' identifier in the f2 function of the 'main' module"
+ "summary": "Replaced the 'fc' identifier with the 'f2' identifier in the f2 function"
},
{
"span": {
@@ -351,7 +366,7 @@
}
]
},
- "summary": "Replaced the 'fd' identifier with the 'f2' identifier in the f2 function of the 'main' module"
+ "summary": "Replaced the 'fd' identifier with the 'f2' identifier in the f2 function"
}
]
},
@@ -380,7 +395,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "25682bee4a82b03d9d7f9ab96c28428ad50270dc..fe1c5c29ff27e556e88630190814a22566eaf082"
+ "shas": "d0160ccee51c30218f5ca3f776ca8c21cf6ccfd2..5e7095ac8137e91c12215c45438bbd29c382290e"
}
,{
"testCaseDescription": "go-function-declarations-delete-insert-test",
@@ -396,7 +411,7 @@
1
],
"end": [
- 8,
+ 9,
1
]
},
@@ -406,13 +421,13 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
]
},
- "summary": "Replaced the 'main' module with the 'main' module"
+ "summary": "Replaced 'package main\n\nfunc main() {\nfunc f1() {}\nfunc f2(a int, b, c, d string) int {}\nfunc f2() (int, error) {}\nfunc f2() (result int, err error) {}\n}\n' at line 1, column 1 - line 9, column 1 with the 'main' module"
}
]
},
@@ -438,7 +453,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "fe1c5c29ff27e556e88630190814a22566eaf082..e5826998ff4221f34b05da09b478a8136e3c4ff0"
+ "shas": "5e7095ac8137e91c12215c45438bbd29c382290e..432d945a039effe38996415a0be25ec7a92dc22f"
}
,{
"testCaseDescription": "go-function-declarations-teardown-test",
@@ -453,12 +468,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -480,5 +510,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e5826998ff4221f34b05da09b478a8136e3c4ff0..e5224329c24b2e2d564a10269e63b36c492d7bf5"
+ "shas": "432d945a039effe38996415a0be25ec7a92dc22f..7ebca2c2e26873ec2ec3d92c6922446eb95bb61f"
}]
diff --git a/test/corpus/diff-summaries/go/function-literals.json b/test/corpus/diff-summaries/go/function-literals.json
index 35ff4777c..95a1b4153 100644
--- a/test/corpus/diff-summaries/go/function-literals.json
+++ b/test/corpus/diff-summaries/go/function-literals.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a5f99e0c9f8b9b96e1f64f8b5fd79ed8c9490ebd..3551d67225e67a496d576b38b507dddf941970af"
+ "shas": "cbd953ad26bc63e3ddd57f753a0d7bf09ed21706..74d2004a9be4bf5167b1d97e6732bbe137e3a460"
}
,{
"testCaseDescription": "go-function-literals-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 's1' var assignment in the main function of the 'main' module"
+ "summary": "Added the 's1' var assignment in the main function"
}
]
},
@@ -83,7 +98,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "3551d67225e67a496d576b38b507dddf941970af..4a0681b812c1080f3b42dcdb472f7cdf6689ca3c"
+ "shas": "74d2004a9be4bf5167b1d97e6732bbe137e3a460..04192192923a0a0e3af386c560b3cd34bc1b63ce"
}
,{
"testCaseDescription": "go-function-literals-replacement-test",
@@ -167,7 +182,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "4a0681b812c1080f3b42dcdb472f7cdf6689ca3c..b8b10ef9de564860494347b02f5e0fe36f915b14"
+ "shas": "04192192923a0a0e3af386c560b3cd34bc1b63ce..0ef7e22a17c2ed105f74e285979fae66528aad70"
}
,{
"testCaseDescription": "go-function-literals-delete-replacement-test",
@@ -251,7 +266,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b8b10ef9de564860494347b02f5e0fe36f915b14..3dfb64b1ce98af88f0435b8cfb6b46ba8a1caa08"
+ "shas": "0ef7e22a17c2ed105f74e285979fae66528aad70..ba516525d99d7da0277fccb9f9ff68aec352e5f3"
}
,{
"testCaseDescription": "go-function-literals-delete-insert-test",
@@ -271,7 +286,7 @@
]
}
},
- "summary": "Deleted the 's1' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 's1' var assignment in the main function"
}
]
},
@@ -296,7 +311,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "3dfb64b1ce98af88f0435b8cfb6b46ba8a1caa08..b48bee5be118ec48670688a78247ef8e8d46a97f"
+ "shas": "ba516525d99d7da0277fccb9f9ff68aec352e5f3..13743127bcf07e1e88a6fc021b0a8b6a698a4a25"
}
,{
"testCaseDescription": "go-function-literals-teardown-test",
@@ -311,12 +326,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -338,5 +368,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b48bee5be118ec48670688a78247ef8e8d46a97f..802da3fcac3bb5bd8d87025c78e2dd27694ea5c4"
+ "shas": "13743127bcf07e1e88a6fc021b0a8b6a698a4a25..bda742d270e92cc83a8a8f229714661cfae58fee"
}]
diff --git a/test/corpus/diff-summaries/go/function-types.json b/test/corpus/diff-summaries/go/function-types.json
index b1e9ff713..c4736513f 100644
--- a/test/corpus/diff-summaries/go/function-types.json
+++ b/test/corpus/diff-summaries/go/function-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "cc8aac0f8db0de4e459571ae4c68771e7c442c63..d0826f8e4f35be91943404925263e1e1e9603357"
+ "shas": "190f44e86419bb122daf395748920e3c5779b66b..1815f5ac7ccb734cfb2c19bc68c7577305301768"
}
,{
"testCaseDescription": "go-function-types-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'a' type declaration in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'b' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'b' type declaration in the main function"
}
]
},
@@ -99,7 +114,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d0826f8e4f35be91943404925263e1e1e9603357..40f24f05af6d2ed0d4b263cf4991347c84103a50"
+ "shas": "1815f5ac7ccb734cfb2c19bc68c7577305301768..3606d9bc10b8730dea35f76b1aa221b078bbadfe"
}
,{
"testCaseDescription": "go-function-types-replacement-test",
@@ -313,7 +328,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "40f24f05af6d2ed0d4b263cf4991347c84103a50..9b9fdaa9a541472468aecf2a623c190ed8aa71bc"
+ "shas": "3606d9bc10b8730dea35f76b1aa221b078bbadfe..58b1cdcdee55c272dae229c1c5118cc6a830596c"
}
,{
"testCaseDescription": "go-function-types-delete-replacement-test",
@@ -527,7 +542,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9b9fdaa9a541472468aecf2a623c190ed8aa71bc..10c85ec2a8794ad974c5931a228bdd533464b5e6"
+ "shas": "58b1cdcdee55c272dae229c1c5118cc6a830596c..f17fbf867be99922b4ceae5821169d4c80acbd6b"
}
,{
"testCaseDescription": "go-function-types-delete-insert-test",
@@ -547,7 +562,7 @@
]
}
},
- "summary": "Deleted the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'a' type declaration in the main function"
},
{
"span": {
@@ -562,7 +577,7 @@
]
}
},
- "summary": "Deleted the 'b' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'b' type declaration in the main function"
}
]
},
@@ -588,7 +603,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "10c85ec2a8794ad974c5931a228bdd533464b5e6..a42e34067a86f039ab807cab9b0f18af0e2af0f6"
+ "shas": "f17fbf867be99922b4ceae5821169d4c80acbd6b..0426718d4af0fec65a3ffdf23db55358449ba5a2"
}
,{
"testCaseDescription": "go-function-types-teardown-test",
@@ -603,12 +618,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -630,5 +660,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a42e34067a86f039ab807cab9b0f18af0e2af0f6..e8d08e2eedd6b2a25ec4649df0ad12534a6c3c09"
+ "shas": "0426718d4af0fec65a3ffdf23db55358449ba5a2..57bf5ffc56480fbb108aa9d683b4dfd5324acbbf"
}]
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 cb2f80cd1..dc92856d8 100644
--- a/test/corpus/diff-summaries/go/go-and-defer-statements.json
+++ b/test/corpus/diff-summaries/go/go-and-defer-statements.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8ae829c0b1cf177164c31d8a3d6678bbc51d20c5..6a61b25a986a2736faaaa06dfb1f4abcf40739dc"
+ "shas": "fa9acd974705290312a7cebdba09b18008dc6093..d00a7d7d9b0063f84a7033c6182913c365412974"
}
,{
"testCaseDescription": "go-go-and-defer-statements-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'x[y]()' defer statement in the main function of the 'main' module"
+ "summary": "Added the 'x[y]()' defer statement in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'x[y]()' go statement in the main function of the 'main' module"
+ "summary": "Added the 'x[y]()' go statement in the main function"
}
]
},
@@ -97,7 +112,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6a61b25a986a2736faaaa06dfb1f4abcf40739dc..913fcfe4be1ad959ae12965780f22e6b6484358a"
+ "shas": "d00a7d7d9b0063f84a7033c6182913c365412974..eafca6f1008f09b4b1a1c39a58d69aa84ac352b6"
}
,{
"testCaseDescription": "go-go-and-defer-statements-replacement-test",
@@ -235,7 +250,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "913fcfe4be1ad959ae12965780f22e6b6484358a..6d08af2b7f337f388175cd015e74670d2b2d0de2"
+ "shas": "eafca6f1008f09b4b1a1c39a58d69aa84ac352b6..949b06caae4bd83cfbfd6a4a2af62754e5426afc"
}
,{
"testCaseDescription": "go-go-and-defer-statements-delete-replacement-test",
@@ -373,7 +388,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6d08af2b7f337f388175cd015e74670d2b2d0de2..8f41e4a938613f3989caee22a4e442573e580e94"
+ "shas": "949b06caae4bd83cfbfd6a4a2af62754e5426afc..6a0c93da8aace8b01e5dcd171ecb9482ec200cb9"
}
,{
"testCaseDescription": "go-go-and-defer-statements-delete-insert-test",
@@ -393,7 +408,7 @@
]
}
},
- "summary": "Deleted the 'x[y]()' defer statement in the main function of the 'main' module"
+ "summary": "Deleted the 'x[y]()' defer statement in the main function"
},
{
"span": {
@@ -408,7 +423,7 @@
]
}
},
- "summary": "Deleted the 'x[y]()' go statement in the main function of the 'main' module"
+ "summary": "Deleted the 'x[y]()' go statement in the main function"
}
]
},
@@ -432,7 +447,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8f41e4a938613f3989caee22a4e442573e580e94..2364dc45f38f6de83d0ee043be6aa264c4d53406"
+ "shas": "6a0c93da8aace8b01e5dcd171ecb9482ec200cb9..8b9931aef1a3b18f61b2dee680cdc1d159cb4f36"
}
,{
"testCaseDescription": "go-go-and-defer-statements-teardown-test",
@@ -447,12 +462,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -474,5 +504,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "2364dc45f38f6de83d0ee043be6aa264c4d53406..27df5c61699f3ed1d465e409ed4793a9a141e7bd"
+ "shas": "8b9931aef1a3b18f61b2dee680cdc1d159cb4f36..43ac69d0304e8f5a93bb985e3f4e05d9dff5d2b6"
}]
diff --git a/test/corpus/diff-summaries/go/grouped-import-declarations.json b/test/corpus/diff-summaries/go/grouped-import-declarations.json
index d2bf6ccc9..18ef1f01e 100644
--- a/test/corpus/diff-summaries/go/grouped-import-declarations.json
+++ b/test/corpus/diff-summaries/go/grouped-import-declarations.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,13 +53,12 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "2c47fd719e136db59fa2b3ccfab4572fe4c1be2c..c6819c24c299e2220e4f833a52987d0ab624030f"
+ "shas": "126db53cee9459e0927b80ed1af574cc273f948e..6b9c8e7943b9fee465f5ae36a8e60f309fd34f53"
}
,{
"testCaseDescription": "go-grouped-import-declarations-insert-test",
"expectedResult": {
- "changes": {},
- "errors": {
+ "changes": {
"grouped-import-declarations.go": [
{
"span": {
@@ -54,12 +68,46 @@
1
],
"end": [
- 8,
- 2
+ 4,
+ 7
]
}
},
- "summary": "Added 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 4, column 1 - line 8, column 2 in the main function of the 'main' module"
+ "summary": "Added the 'import' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 11
+ ]
+ }
+ },
+ "summary": "Added the \"net/http\" string in the main function"
+ }
+ ]
+ },
+ "errors": {
+ "grouped-import-declarations.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 3
+ ],
+ "end": [
+ 7,
+ 23
+ ]
+ }
+ },
+ "summary": "Added '. \"some/dsl\"\n alias \"some/package\"' at line 6, column 3 - line 7, column 23 in the main function"
}
]
}
@@ -85,7 +133,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c6819c24c299e2220e4f833a52987d0ab624030f..19482fe3d5e6dddd8e28228c1af0952ceac64894"
+ "shas": "6b9c8e7943b9fee465f5ae36a8e60f309fd34f53..da13ed2e396030607a1566cd6b4aa3295a2d1221"
}
,{
"testCaseDescription": "go-grouped-import-declarations-replacement-test",
@@ -117,7 +165,7 @@
}
]
},
- "summary": "Replaced the \"net/http\" string with the \"net/socket\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"net/http\" string with the \"net/socket\" string in the main function"
},
{
"span": {
@@ -144,7 +192,7 @@
}
]
},
- "summary": "Replaced the \"some/dsl\" string with the \"types/dsl\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"some/dsl\" string with the \"types/dsl\" string in the main function"
},
{
"span": {
@@ -171,7 +219,7 @@
}
]
},
- "summary": "Replaced the \"some/package\" string with the \"awesome/package\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"some/package\" string with the \"awesome/package\" string in the main function"
}
]
},
@@ -199,7 +247,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "19482fe3d5e6dddd8e28228c1af0952ceac64894..99e842e6e87b98e39d823e8d6c543d41ee49ed2c"
+ "shas": "da13ed2e396030607a1566cd6b4aa3295a2d1221..d10a69e54f224c4a48b4ab0489e435f86ac84de1"
}
,{
"testCaseDescription": "go-grouped-import-declarations-delete-replacement-test",
@@ -231,7 +279,7 @@
}
]
},
- "summary": "Replaced the \"net/socket\" string with the \"net/http\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"net/socket\" string with the \"net/http\" string in the main function"
},
{
"span": {
@@ -258,7 +306,7 @@
}
]
},
- "summary": "Replaced the \"types/dsl\" string with the \"some/dsl\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"types/dsl\" string with the \"some/dsl\" string in the main function"
},
{
"span": {
@@ -285,7 +333,7 @@
}
]
},
- "summary": "Replaced the \"awesome/package\" string with the \"some/package\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"awesome/package\" string with the \"some/package\" string in the main function"
}
]
},
@@ -313,13 +361,12 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "99e842e6e87b98e39d823e8d6c543d41ee49ed2c..25c7452f65645a864deb0d14a037205de2740e2f"
+ "shas": "d10a69e54f224c4a48b4ab0489e435f86ac84de1..6a25d985a312ed1935f33359735bfc3fad514a37"
}
,{
"testCaseDescription": "go-grouped-import-declarations-delete-insert-test",
"expectedResult": {
- "changes": {},
- "errors": {
+ "changes": {
"grouped-import-declarations.go": [
{
"span": {
@@ -329,12 +376,46 @@
1
],
"end": [
- 8,
- 2
+ 4,
+ 7
]
}
},
- "summary": "Deleted 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 4, column 1 - line 8, column 2 in the main function of the 'main' module"
+ "summary": "Deleted the 'import' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 11
+ ]
+ }
+ },
+ "summary": "Deleted the \"net/http\" string in the main function"
+ }
+ ]
+ },
+ "errors": {
+ "grouped-import-declarations.go": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 3
+ ],
+ "end": [
+ 7,
+ 23
+ ]
+ }
+ },
+ "summary": "Deleted '. \"some/dsl\"\n alias \"some/package\"' at line 6, column 3 - line 7, column 23 in the main function"
}
]
}
@@ -360,7 +441,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "25c7452f65645a864deb0d14a037205de2740e2f..baf2152faedc0a6facf152568c6b680c7e52fd86"
+ "shas": "6a25d985a312ed1935f33359735bfc3fad514a37..0b75622a824ba8367f3f6dee95cfdccbfcc4eb8f"
}
,{
"testCaseDescription": "go-grouped-import-declarations-teardown-test",
@@ -375,12 +456,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -402,5 +498,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "baf2152faedc0a6facf152568c6b680c7e52fd86..038d3fd0f1c08ca004a0a2d0c61ecc27b0535e67"
+ "shas": "0b75622a824ba8367f3f6dee95cfdccbfcc4eb8f..d4d30589c4945d693f9b6b7e327ddbcd45e70321"
}]
diff --git a/test/corpus/diff-summaries/go/grouped-var-declarations.json b/test/corpus/diff-summaries/go/grouped-var-declarations.json
index 23f622453..9005c80a8 100644
--- a/test/corpus/diff-summaries/go/grouped-var-declarations.json
+++ b/test/corpus/diff-summaries/go/grouped-var-declarations.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e75c5ac355ded95806073c70e83be9e9b3634163..79a6631220e4e84f5dcce34f797e4144d06d4962"
+ "shas": "3dba2a559a0cc46933a2663e7b9cdcd4a92808d9..24b5a7da7f83d445e406076f4e5cd0eb29b81187"
}
,{
"testCaseDescription": "go-grouped-var-declarations-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'zero' var assignment in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'one' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'one' var assignment in the main function"
}
]
},
@@ -99,7 +114,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "79a6631220e4e84f5dcce34f797e4144d06d4962..06f0d2493c8d5b70a8dee0ee3905f151ea506795"
+ "shas": "24b5a7da7f83d445e406076f4e5cd0eb29b81187..47a9982c7ce46ecab0a4eea473b1e0e63686a8fd"
}
,{
"testCaseDescription": "go-grouped-var-declarations-replacement-test",
@@ -184,7 +199,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "06f0d2493c8d5b70a8dee0ee3905f151ea506795..f73a7fc0adae36e82e2aaeb5d696abea6b23a3fb"
+ "shas": "47a9982c7ce46ecab0a4eea473b1e0e63686a8fd..e12f033c84f4d6f59ae1e0542ed68873634f85ff"
}
,{
"testCaseDescription": "go-grouped-var-declarations-delete-replacement-test",
@@ -269,7 +284,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "f73a7fc0adae36e82e2aaeb5d696abea6b23a3fb..035552bf16bcde92ba554125718245d842b7d9d3"
+ "shas": "e12f033c84f4d6f59ae1e0542ed68873634f85ff..0df3b93f76d7331db5126eb444c15d5ef2829485"
}
,{
"testCaseDescription": "go-grouped-var-declarations-delete-insert-test",
@@ -289,7 +304,7 @@
]
}
},
- "summary": "Deleted the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'zero' var assignment in the main function"
},
{
"span": {
@@ -304,7 +319,7 @@
]
}
},
- "summary": "Deleted the 'one' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'one' var assignment in the main function"
}
]
},
@@ -330,7 +345,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "035552bf16bcde92ba554125718245d842b7d9d3..d30e22d42d938d8dc1099d7fb7f6e692aad85407"
+ "shas": "0df3b93f76d7331db5126eb444c15d5ef2829485..c681a4b6c5b308af84285b1b48b80d02adb0dba3"
}
,{
"testCaseDescription": "go-grouped-var-declarations-teardown-test",
@@ -345,12 +360,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -372,5 +402,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d30e22d42d938d8dc1099d7fb7f6e692aad85407..6e1ebffb2ad214b1c4a7ab7a8efed9b6a25e8470"
+ "shas": "c681a4b6c5b308af84285b1b48b80d02adb0dba3..08c2e3dcd4ce51ddc9fd673ef182af5f0748761d"
}]
diff --git a/test/corpus/diff-summaries/go/if-statements.json b/test/corpus/diff-summaries/go/if-statements.json
index 66b1b24db..6eab0a4f5 100644
--- a/test/corpus/diff-summaries/go/if-statements.json
+++ b/test/corpus/diff-summaries/go/if-statements.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "2d4500613c50791e41a932edd1885da8e9830f8e..c98826eee37b8054f73558f3295f06a90ca954c1"
+ "shas": "3f2a09bd95dfbff3712c14095a53c1f0a3855648..003b74b612db2ce7c8b3cafa4767e2d93c80857b"
}
,{
"testCaseDescription": "go-if-statements-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a()' if statement in the main function of the 'main' module"
+ "summary": "Added the 'a()' if statement in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'a := b(); c' if statement in the main function of the 'main' module"
+ "summary": "Added the 'a := b()' if statement in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 'a()' if statement in the main function of the 'main' module"
+ "summary": "Added the 'a()' if statement in the main function"
}
]
},
@@ -121,7 +136,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c98826eee37b8054f73558f3295f06a90ca954c1..8d270696b97d37fa644ea92e22e8f8aaff35c2ff"
+ "shas": "003b74b612db2ce7c8b3cafa4767e2d93c80857b..90a41d97fa0420b82f8d8d7b550dd92171663b0f"
}
,{
"testCaseDescription": "go-if-statements-replacement-test",
@@ -180,7 +195,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'y' identifier in the y var assignment of the 'main' function"
+ "summary": "Replaced the 'a' identifier with the 'y' identifier in the 'y := b()' if statement of the 'main' function"
},
{
"span": {
@@ -240,7 +255,7 @@
" c()"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8d270696b97d37fa644ea92e22e8f8aaff35c2ff..88d296f03520e7b0c4358f9b31cb5c8098fb763b"
+ "shas": "90a41d97fa0420b82f8d8d7b550dd92171663b0f..5b8d17f1bd7bf95dece870548aa1a2dc603ae25c"
}
,{
"testCaseDescription": "go-if-statements-delete-replacement-test",
@@ -299,7 +314,7 @@
}
]
},
- "summary": "Replaced the 'y' identifier with the 'a' identifier in the a var assignment of the 'main' function"
+ "summary": "Replaced the 'y' identifier with the 'a' identifier in the 'a := b()' if statement of the 'main' function"
},
{
"span": {
@@ -359,7 +374,7 @@
" c()"
],
"gitDir": "test/corpus/repos/go",
- "shas": "88d296f03520e7b0c4358f9b31cb5c8098fb763b..37697f71afa721d3e1b6be5604618344b856808a"
+ "shas": "5b8d17f1bd7bf95dece870548aa1a2dc603ae25c..2c0ac08501ad5b8bc5e1383946ac2adc645a1102"
}
,{
"testCaseDescription": "go-if-statements-delete-insert-test",
@@ -379,7 +394,7 @@
]
}
},
- "summary": "Deleted the 'a()' if statement in the main function of the 'main' module"
+ "summary": "Deleted the 'a()' if statement in the main function"
},
{
"span": {
@@ -394,7 +409,7 @@
]
}
},
- "summary": "Deleted the 'a := b(); c' if statement in the main function of the 'main' module"
+ "summary": "Deleted the 'a := b()' if statement in the main function"
},
{
"span": {
@@ -409,7 +424,7 @@
]
}
},
- "summary": "Deleted the 'a()' if statement in the main function of the 'main' module"
+ "summary": "Deleted the 'a()' if statement in the main function"
}
]
},
@@ -442,7 +457,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "37697f71afa721d3e1b6be5604618344b856808a..d216b0b498b90c21e79ccadfedd6c57e66289d1c"
+ "shas": "2c0ac08501ad5b8bc5e1383946ac2adc645a1102..ca18125942a9a260c9187e56d003f1b21e71002f"
}
,{
"testCaseDescription": "go-if-statements-teardown-test",
@@ -457,12 +472,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -484,5 +514,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d216b0b498b90c21e79ccadfedd6c57e66289d1c..b534a2624a6f74eebed7bd6da21bc7df27018a96"
+ "shas": "ca18125942a9a260c9187e56d003f1b21e71002f..e3c2411f013b063d1c440d3a295be6485170c63d"
}]
diff --git a/test/corpus/diff-summaries/go/imaginary-literals.json b/test/corpus/diff-summaries/go/imaginary-literals.json
index 65690ab25..088e5dcda 100644
--- a/test/corpus/diff-summaries/go/imaginary-literals.json
+++ b/test/corpus/diff-summaries/go/imaginary-literals.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a43f5210e8e5da594371eacab324e27889547ce0..aad2c18c5e34b74bf3c0326af866aa1031297abf"
+ "shas": "fd41bb91afdd6087f0c3e6c54566857b7105df8c..5712b1395e13d1c0fa00cffacbf8bc0951053d35"
}
,{
"testCaseDescription": "go-imaginary-literals-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'a' var assignment in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'b' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'b' var assignment in the main function"
}
]
},
@@ -99,7 +114,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "aad2c18c5e34b74bf3c0326af866aa1031297abf..1e90859d681fb50b514a36f0a4d00fa96c1f0331"
+ "shas": "5712b1395e13d1c0fa00cffacbf8bc0951053d35..22932b78378effd2b941d482834bf0a72286edec"
}
,{
"testCaseDescription": "go-imaginary-literals-replacement-test",
@@ -184,7 +199,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "1e90859d681fb50b514a36f0a4d00fa96c1f0331..71841ec35c87085fe43e09014faf9d861f63307a"
+ "shas": "22932b78378effd2b941d482834bf0a72286edec..9f5d0bbee0d79018b1b0187ba73c28d0f9d72c78"
}
,{
"testCaseDescription": "go-imaginary-literals-delete-replacement-test",
@@ -269,7 +284,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "71841ec35c87085fe43e09014faf9d861f63307a..978db2c8b0ffe2143eb8a281234c6129fa285e9a"
+ "shas": "9f5d0bbee0d79018b1b0187ba73c28d0f9d72c78..30a750a5c56e53a8f94fcc56d10cca85093b2286"
}
,{
"testCaseDescription": "go-imaginary-literals-delete-insert-test",
@@ -289,7 +304,7 @@
]
}
},
- "summary": "Deleted the 'a' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'a' var assignment in the main function"
},
{
"span": {
@@ -304,7 +319,7 @@
]
}
},
- "summary": "Deleted the 'b' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'b' var assignment in the main function"
}
]
},
@@ -330,7 +345,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "978db2c8b0ffe2143eb8a281234c6129fa285e9a..25724e370d9a7945d55448d91da88ab0001fcebc"
+ "shas": "30a750a5c56e53a8f94fcc56d10cca85093b2286..9b4c1d9f9789b88f196087dafbad93a21508c9c2"
}
,{
"testCaseDescription": "go-imaginary-literals-teardown-test",
@@ -345,12 +360,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -372,5 +402,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "25724e370d9a7945d55448d91da88ab0001fcebc..1ed63b35351e352f6ae6a546bb49920585747c54"
+ "shas": "9b4c1d9f9789b88f196087dafbad93a21508c9c2..d39cc6bcd81255864bc210bd0ab92a71c0a80cc2"
}]
diff --git a/test/corpus/diff-summaries/go/increment-decrement-statements.json b/test/corpus/diff-summaries/go/increment-decrement-statements.json
index 14d9f1635..6f0516bf4 100644
--- a/test/corpus/diff-summaries/go/increment-decrement-statements.json
+++ b/test/corpus/diff-summaries/go/increment-decrement-statements.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "adb2401da7e74b66c885cf959788358c7ba5c3ee..59dcf1fcc48c84b1a9938e79d788af6b13a328a8"
+ "shas": "bb4ba3185a52b92f422411ad6cae97a82e2b2657..16dda00e283e0850677a63b7e489cf83d5c5a5b6"
}
,{
"testCaseDescription": "go-increment-decrement-statements-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'i++' increment statement in the main function of the 'main' module"
+ "summary": "Added the 'i++' increment statement in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'j--' decrement statement in the main function of the 'main' module"
+ "summary": "Added the 'j--' decrement statement in the main function"
}
]
},
@@ -97,7 +112,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "59dcf1fcc48c84b1a9938e79d788af6b13a328a8..b2a71db8b841f85ec6d62c4ee5cb758a502bfcb3"
+ "shas": "16dda00e283e0850677a63b7e489cf83d5c5a5b6..741d8660e0bf62db6265e192fd6b90e50b9eef4f"
}
,{
"testCaseDescription": "go-increment-decrement-statements-replacement-test",
@@ -129,7 +144,7 @@
}
]
},
- "summary": "Replaced the 'i++' increment statement with the 'foo++' increment statement in the main function of the 'main' module"
+ "summary": "Replaced the 'i++' increment statement with the 'foo++' increment statement in the main function"
},
{
"span": {
@@ -144,7 +159,7 @@
]
}
},
- "summary": "Added the 'x++' increment statement in the main function of the 'main' module"
+ "summary": "Added the 'x++' increment statement in the main function"
},
{
"span": {
@@ -159,7 +174,7 @@
]
}
},
- "summary": "Deleted the 'j--' decrement statement in the main function of the 'main' module"
+ "summary": "Deleted the 'j--' decrement statement in the main function"
}
]
},
@@ -184,7 +199,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b2a71db8b841f85ec6d62c4ee5cb758a502bfcb3..6b16aefff065ed5a41e6891dd94ad040e85f312b"
+ "shas": "741d8660e0bf62db6265e192fd6b90e50b9eef4f..a0c075e89018b1d3e99ed50b0462c9c6fe12e267"
}
,{
"testCaseDescription": "go-increment-decrement-statements-delete-replacement-test",
@@ -216,7 +231,7 @@
}
]
},
- "summary": "Replaced the 'foo++' increment statement with the 'i++' increment statement in the main function of the 'main' module"
+ "summary": "Replaced the 'foo++' increment statement with the 'i++' increment statement in the main function"
},
{
"span": {
@@ -231,7 +246,7 @@
]
}
},
- "summary": "Added the 'j--' decrement statement in the main function of the 'main' module"
+ "summary": "Added the 'j--' decrement statement in the main function"
},
{
"span": {
@@ -246,7 +261,7 @@
]
}
},
- "summary": "Deleted the 'x++' increment statement in the main function of the 'main' module"
+ "summary": "Deleted the 'x++' increment statement in the main function"
}
]
},
@@ -271,7 +286,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6b16aefff065ed5a41e6891dd94ad040e85f312b..cceed70a20fed7d8cd1d84eb6800ca37ea02bc01"
+ "shas": "a0c075e89018b1d3e99ed50b0462c9c6fe12e267..251078b70b5dafb8b9a682ec094530dfb8c39572"
}
,{
"testCaseDescription": "go-increment-decrement-statements-delete-insert-test",
@@ -291,7 +306,7 @@
]
}
},
- "summary": "Deleted the 'i++' increment statement in the main function of the 'main' module"
+ "summary": "Deleted the 'i++' increment statement in the main function"
},
{
"span": {
@@ -306,7 +321,7 @@
]
}
},
- "summary": "Deleted the 'j--' decrement statement in the main function of the 'main' module"
+ "summary": "Deleted the 'j--' decrement statement in the main function"
}
]
},
@@ -330,7 +345,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "cceed70a20fed7d8cd1d84eb6800ca37ea02bc01..f82a411f0daeb75a2800293d5651522df8f1bbd6"
+ "shas": "251078b70b5dafb8b9a682ec094530dfb8c39572..759e0718fcbd72afbcc54da11715a66d338f9696"
}
,{
"testCaseDescription": "go-increment-decrement-statements-teardown-test",
@@ -345,12 +360,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -372,5 +402,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "f82a411f0daeb75a2800293d5651522df8f1bbd6..9b6482e7bca1a74c6ecdc400cf0ed146ebb6a29a"
+ "shas": "759e0718fcbd72afbcc54da11715a66d338f9696..e86ae4b80ecf2b01260ea4afc56327253ab59646"
}]
diff --git a/test/corpus/diff-summaries/go/indexing-expressions.json b/test/corpus/diff-summaries/go/indexing-expressions.json
index 0c9ce8e26..d70b00908 100644
--- a/test/corpus/diff-summaries/go/indexing-expressions.json
+++ b/test/corpus/diff-summaries/go/indexing-expressions.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "54cc2c98c56816e321a4fffb6927c2793f3cc794..d19eab9ef64c9690bb40f960167fe7f379050ce1"
+ "shas": "0a55a88480be2cc766ee756b5b5f7bf45704376c..4f60b48123030197c6618ae645a4374972ea4c36"
}
,{
"testCaseDescription": "go-indexing-expressions-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a[1]' index expression in the main function of the 'main' module"
+ "summary": "Added the 'a[1]' index expression in the main function"
},
{
"span": {
@@ -69,11 +84,11 @@
],
"end": [
5,
- 6
+ 3
]
}
},
- "summary": "Added the 'b[b[:]]' slice literal in the main function of the 'main' module"
+ "summary": "Added the 'b' identifier in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 'c[1]' slice literal in the main function of the 'main' module"
+ "summary": "Added the 'c[1]' slice literal in the main function"
},
{
"span": {
@@ -99,41 +114,146 @@
],
"end": [
7,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'd' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 4
+ ],
+ "end": [
+ 7,
+ 5
+ ]
+ }
+ },
+ "summary": "Added '1' in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 7,
+ 6
+ ],
+ "end": [
+ 7,
+ 7
+ ]
+ }
+ },
+ "summary": "Added '2' in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 2
+ ],
+ "end": [
+ 8,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'e' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 5
+ ],
+ "end": [
+ 8,
+ 6
+ ]
+ }
+ },
+ "summary": "Added '2' in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 7
+ ],
+ "end": [
+ 8,
8
]
}
},
- "summary": "Added the 'd[1:2]' slice literal in the main function of the 'main' module"
+ "summary": "Added '3' in the main function"
},
{
"span": {
"insert": {
"start": [
- 8,
+ 9,
2
],
"end": [
- 8,
+ 9,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'f' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 4
+ ],
+ "end": [
+ 9,
+ 5
+ ]
+ }
+ },
+ "summary": "Added '1' in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 6
+ ],
+ "end": [
+ 9,
+ 7
+ ]
+ }
+ },
+ "summary": "Added '2' in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 9,
+ 8
+ ],
+ "end": [
+ 9,
9
]
}
},
- "summary": "Added the 'e[2:3]' slice literal in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 9,
- 2
- ],
- "end": [
- 9,
- 10
- ]
- }
- },
- "summary": "Added the 'f[1:2:3]' slice literal in the main function of the 'main' module"
+ "summary": "Added '3' in the main function"
}
]
},
@@ -161,7 +281,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d19eab9ef64c9690bb40f960167fe7f379050ce1..7b7e60ce9893393670010e1b0c82c393d0bbc87f"
+ "shas": "4f60b48123030197c6618ae645a4374972ea4c36..cd7d3053acc66aa2f4d9f3971970b1d3291a7a59"
}
,{
"testCaseDescription": "go-indexing-expressions-replacement-test",
@@ -181,7 +301,7 @@
]
}
},
- "summary": "Added the 'z[2]' slice literal in the main function of the 'main' module"
+ "summary": "Added the 'z[2]' slice literal in the main function"
},
{
"span": {
@@ -196,7 +316,7 @@
]
}
},
- "summary": "Added the 'y[1]' slice literal in the main function of the 'main' module"
+ "summary": "Added the 'y[1]' slice literal in the main function"
},
{
"span": {
@@ -211,7 +331,7 @@
]
}
},
- "summary": "Added the 'x[1]' slice literal in the main function of the 'main' module"
+ "summary": "Added the 'x[1]' slice literal in the main function"
},
{
"span": {
@@ -226,7 +346,7 @@
]
}
},
- "summary": "Deleted the 'a[1]' index expression in the main function of the 'main' module"
+ "summary": "Deleted the 'a[1]' index expression in the main function"
},
{
"span": {
@@ -237,11 +357,11 @@
],
"end": [
5,
- 6
+ 3
]
}
},
- "summary": "Deleted the 'b[b[:]]' slice literal in the main function of the 'main' module"
+ "summary": "Deleted the 'b' identifier in the main function"
},
{
"span": {
@@ -256,7 +376,7 @@
]
}
},
- "summary": "Deleted the 'c[1]' slice literal in the main function of the 'main' module"
+ "summary": "Deleted the 'c[1]' slice literal in the main function"
}
]
},
@@ -285,7 +405,7 @@
" f[1:2:3]"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7b7e60ce9893393670010e1b0c82c393d0bbc87f..3cb474bb7624520b7d6f16188a5949810d92dd20"
+ "shas": "cd7d3053acc66aa2f4d9f3971970b1d3291a7a59..c84e151f812ae561b1912638e0585fe32d854242"
}
,{
"testCaseDescription": "go-indexing-expressions-delete-replacement-test",
@@ -305,7 +425,22 @@
]
}
},
- "summary": "Added the 'a[1]' index expression in the main function of the 'main' module"
+ "summary": "Added the 'a[1]' index expression in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 2
+ ],
+ "end": [
+ 5,
+ 3
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier in the main function"
},
{
"span": {
@@ -322,59 +457,59 @@
},
{
"start": [
- 5,
+ 6,
2
],
"end": [
- 5,
+ 6,
3
]
}
]
},
- "summary": "Replaced the 'z' identifier with the 'b' identifier in the b[b[:]] slice literal of the 'main' function"
- },
- {
- "span": {
- "delete": {
- "start": [
- 4,
- 4
- ],
- "end": [
- 4,
- 5
- ]
- }
- },
- "summary": "Deleted '2' in the b[b[:]] slice literal of the 'main' function"
+ "summary": "Replaced the 'z' identifier with the 'c' identifier in the c[1] slice literal of the 'main' function"
},
{
"span": {
"replace": [
{
"start": [
- 5,
- 2
+ 4,
+ 4
],
"end": [
- 5,
- 3
+ 4,
+ 5
]
},
{
"start": [
6,
- 2
+ 4
],
"end": [
6,
- 3
+ 5
]
}
]
},
- "summary": "Replaced the 'y' identifier with the 'c' identifier in the c[1] slice literal of the 'main' function"
+ "summary": "Replaced '2' with '1' in the c[1] slice literal of the 'main' function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 2
+ ],
+ "end": [
+ 5,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted the 'y[1]' slice literal in the main function"
},
{
"span": {
@@ -389,7 +524,7 @@
]
}
},
- "summary": "Deleted the 'x[1]' slice literal in the main function of the 'main' module"
+ "summary": "Deleted the 'x[1]' slice literal in the main function"
}
]
},
@@ -418,7 +553,7 @@
" f[1:2:3]"
],
"gitDir": "test/corpus/repos/go",
- "shas": "3cb474bb7624520b7d6f16188a5949810d92dd20..2ca22a76ba48f867fd999d0f99608d38b55809fc"
+ "shas": "c84e151f812ae561b1912638e0585fe32d854242..08a032f27c171ad3d26321259c510b30cf268471"
}
,{
"testCaseDescription": "go-indexing-expressions-delete-insert-test",
@@ -438,7 +573,7 @@
]
}
},
- "summary": "Deleted the 'a[1]' index expression in the main function of the 'main' module"
+ "summary": "Deleted the 'a[1]' index expression in the main function"
},
{
"span": {
@@ -449,11 +584,11 @@
],
"end": [
5,
- 6
+ 3
]
}
},
- "summary": "Deleted the 'b[b[:]]' slice literal in the main function of the 'main' module"
+ "summary": "Deleted the 'b' identifier in the main function"
},
{
"span": {
@@ -468,7 +603,7 @@
]
}
},
- "summary": "Deleted the 'c[1]' slice literal in the main function of the 'main' module"
+ "summary": "Deleted the 'c[1]' slice literal in the main function"
},
{
"span": {
@@ -479,41 +614,146 @@
],
"end": [
7,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'd' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 4
+ ],
+ "end": [
+ 7,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted '1' in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 7,
+ 6
+ ],
+ "end": [
+ 7,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted '2' in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 2
+ ],
+ "end": [
+ 8,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'e' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 5
+ ],
+ "end": [
+ 8,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted '2' in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 8,
+ 7
+ ],
+ "end": [
+ 8,
8
]
}
},
- "summary": "Deleted the 'd[1:2]' slice literal in the main function of the 'main' module"
+ "summary": "Deleted '3' in the main function"
},
{
"span": {
"delete": {
"start": [
- 8,
+ 9,
2
],
"end": [
- 8,
+ 9,
+ 3
+ ]
+ }
+ },
+ "summary": "Deleted the 'f' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 9,
+ 4
+ ],
+ "end": [
+ 9,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted '1' in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 9,
+ 6
+ ],
+ "end": [
+ 9,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted '2' in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 9,
+ 8
+ ],
+ "end": [
+ 9,
9
]
}
},
- "summary": "Deleted the 'e[2:3]' slice literal in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 9,
- 2
- ],
- "end": [
- 9,
- 10
- ]
- }
- },
- "summary": "Deleted the 'f[1:2:3]' slice literal in the main function of the 'main' module"
+ "summary": "Deleted '3' in the main function"
}
]
},
@@ -541,7 +781,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "2ca22a76ba48f867fd999d0f99608d38b55809fc..dd710f15cf06e30adfc658dabf70fbbd8b0958fa"
+ "shas": "08a032f27c171ad3d26321259c510b30cf268471..6f372cae9a7ae4a00c120150faa8316627b50f7d"
}
,{
"testCaseDescription": "go-indexing-expressions-teardown-test",
@@ -556,12 +796,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -583,5 +838,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "dd710f15cf06e30adfc658dabf70fbbd8b0958fa..668c02674516194c0623120c957d1be93af6cde5"
+ "shas": "6f372cae9a7ae4a00c120150faa8316627b50f7d..39c039e08c3764d56d26a74bbc7bb32704cc398c"
}]
diff --git a/test/corpus/diff-summaries/go/int-literals.json b/test/corpus/diff-summaries/go/int-literals.json
index 3e844f9a2..b52305401 100644
--- a/test/corpus/diff-summaries/go/int-literals.json
+++ b/test/corpus/diff-summaries/go/int-literals.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,12 +53,13 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "038d3fd0f1c08ca004a0a2d0c61ecc27b0535e67..b49dc2a86107a6125c6c6b5b27a10b97c349c951"
+ "shas": "d4d30589c4945d693f9b6b7e327ddbcd45e70321..35712f9936e6e990151f65bd8282f587c311283f"
}
,{
"testCaseDescription": "go-int-literals-insert-test",
"expectedResult": {
- "changes": {
+ "changes": {},
+ "errors": {
"int-literals.go": [
{
"span": {
@@ -52,32 +68,16 @@
5,
1
],
- "end": [
- 5,
- 9
- ]
- }
- },
- "summary": "Added the 'a' var assignment in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 12
- ],
"end": [
5,
20
]
}
},
- "summary": "Added the '2' var assignment in the main function of the 'main' module"
+ "summary": "Added 'a = 1, b = 2, c = 3' at line 5, column 1 - line 5, column 20 in the main function"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"int-literals.go"
@@ -98,7 +98,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b49dc2a86107a6125c6c6b5b27a10b97c349c951..7922f4a2649ec54d9aa444582b20ef48b8a0c49b"
+ "shas": "35712f9936e6e990151f65bd8282f587c311283f..c4fbea18faece138b1ca16fac7c135aacab7e026"
}
,{
"testCaseDescription": "go-int-literals-replacement-test",
@@ -157,7 +157,7 @@
}
]
},
- "summary": "Replaced '2' with '5' in the 5 var assignment of the 'main' function"
+ "summary": "Replaced '2' with '5' in an assignment to 5, c of the 'main' function"
},
{
"span": {
@@ -184,7 +184,7 @@
}
]
},
- "summary": "Replaced '3' with '6' in the 5 var assignment of the 'main' function"
+ "summary": "Replaced '3' with '6' in an assignment to 5, c of the 'main' function"
}
]
},
@@ -208,7 +208,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7922f4a2649ec54d9aa444582b20ef48b8a0c49b..e978725a447db93523c51453ac03fe50b8f32e8f"
+ "shas": "c4fbea18faece138b1ca16fac7c135aacab7e026..5a4da82a60dae3adac65138408a1c9c13c9341ed"
}
,{
"testCaseDescription": "go-int-literals-delete-replacement-test",
@@ -267,7 +267,7 @@
}
]
},
- "summary": "Replaced '5' with '2' in the 2 var assignment of the 'main' function"
+ "summary": "Replaced '5' with '2' in an assignment to 2, c of the 'main' function"
},
{
"span": {
@@ -294,7 +294,7 @@
}
]
},
- "summary": "Replaced '6' with '3' in the 2 var assignment of the 'main' function"
+ "summary": "Replaced '6' with '3' in an assignment to 2, c of the 'main' function"
}
]
},
@@ -318,12 +318,13 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e978725a447db93523c51453ac03fe50b8f32e8f..8801fe8fbe85f6c7fde621d02bb69ae1d8d2f117"
+ "shas": "5a4da82a60dae3adac65138408a1c9c13c9341ed..7afa4043deb1d962815d430c79d37af59f929d69"
}
,{
"testCaseDescription": "go-int-literals-delete-insert-test",
"expectedResult": {
- "changes": {
+ "changes": {},
+ "errors": {
"int-literals.go": [
{
"span": {
@@ -332,32 +333,16 @@
5,
1
],
- "end": [
- 5,
- 9
- ]
- }
- },
- "summary": "Deleted the 'a' var assignment in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 12
- ],
"end": [
5,
20
]
}
},
- "summary": "Deleted the '2' var assignment in the main function of the 'main' module"
+ "summary": "Deleted 'a = 1, b = 2, c = 3' at line 5, column 1 - line 5, column 20 in the main function"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"int-literals.go"
@@ -378,7 +363,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8801fe8fbe85f6c7fde621d02bb69ae1d8d2f117..508d9327fa16fb7a1a03998a5214526d9c6bebf0"
+ "shas": "7afa4043deb1d962815d430c79d37af59f929d69..9db47a4be9cce6edd5a54ffc93d311fb8ec7bd84"
}
,{
"testCaseDescription": "go-int-literals-teardown-test",
@@ -393,12 +378,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -420,5 +420,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "508d9327fa16fb7a1a03998a5214526d9c6bebf0..091bc58290f6343880a29ef209a9d87aa7a3fcc0"
+ "shas": "9db47a4be9cce6edd5a54ffc93d311fb8ec7bd84..65295513fb69f053f466c62e25b12d37872a7543"
}]
diff --git a/test/corpus/diff-summaries/go/interface-types.json b/test/corpus/diff-summaries/go/interface-types.json
index c9a66c531..90d9c28a1 100644
--- a/test/corpus/diff-summaries/go/interface-types.json
+++ b/test/corpus/diff-summaries/go/interface-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "80f368e3e339a6f6cd13071fff11a504b589ebaa..fed0e7aa61d5c427a357795cbab25ac4992d6307"
+ "shas": "d27aeb5e58d624d463c84b7a506673945bee82fd..6457603d8983b1317a9b928ea207eb6edd64f594"
}
,{
"testCaseDescription": "go-interface-types-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'i1' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'i1' type declaration in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'i2' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'i2' type declaration in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 'i3' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'i3' type declaration in the main function"
}
]
},
@@ -117,7 +132,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "fed0e7aa61d5c427a357795cbab25ac4992d6307..4c36f6466089c121fbcd9047274f757155b0462f"
+ "shas": "6457603d8983b1317a9b928ea207eb6edd64f594..56cfa1522cfdcdac970e3fafdd705c56945226cf"
}
,{
"testCaseDescription": "go-interface-types-replacement-test",
@@ -232,7 +247,7 @@
" SomeMethod(s string) error"
],
"gitDir": "test/corpus/repos/go",
- "shas": "4c36f6466089c121fbcd9047274f757155b0462f..71c93c1227a15f14856489f78b757630be715422"
+ "shas": "56cfa1522cfdcdac970e3fafdd705c56945226cf..a0b32c300b7848b5de8c996337254fba410a49ff"
}
,{
"testCaseDescription": "go-interface-types-delete-replacement-test",
@@ -347,7 +362,7 @@
" SomeMethod(s string) error"
],
"gitDir": "test/corpus/repos/go",
- "shas": "71c93c1227a15f14856489f78b757630be715422..d28b95cd4d1b0ce38f2a6a41b9299929b5e547d3"
+ "shas": "a0b32c300b7848b5de8c996337254fba410a49ff..e7baf12e7fdd8b0ae0849f70632a5b7730771d40"
}
,{
"testCaseDescription": "go-interface-types-delete-insert-test",
@@ -367,7 +382,7 @@
]
}
},
- "summary": "Deleted the 'i1' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'i1' type declaration in the main function"
},
{
"span": {
@@ -382,7 +397,7 @@
]
}
},
- "summary": "Deleted the 'i2' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'i2' type declaration in the main function"
},
{
"span": {
@@ -397,7 +412,7 @@
]
}
},
- "summary": "Deleted the 'i3' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'i3' type declaration in the main function"
}
]
},
@@ -426,7 +441,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d28b95cd4d1b0ce38f2a6a41b9299929b5e547d3..3833ebb48a526a3a7eef7b4f7d939cf60eaf88be"
+ "shas": "e7baf12e7fdd8b0ae0849f70632a5b7730771d40..b3a1c76dfcde365828f3aca43ca12cc93ba6fed7"
}
,{
"testCaseDescription": "go-interface-types-teardown-test",
@@ -441,12 +456,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -468,5 +498,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "3833ebb48a526a3a7eef7b4f7d939cf60eaf88be..08a4feef4554fd83bb199f7d6aa2017f2d5dcf95"
+ "shas": "b3a1c76dfcde365828f3aca43ca12cc93ba6fed7..749bfb72d276ee57a9c014001d350bb1f642f2a9"
}]
diff --git a/test/corpus/diff-summaries/go/label-statements.json b/test/corpus/diff-summaries/go/label-statements.json
index 9daa078e2..4ffb69eca 100644
--- a/test/corpus/diff-summaries/go/label-statements.json
+++ b/test/corpus/diff-summaries/go/label-statements.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "27df5c61699f3ed1d465e409ed4793a9a141e7bd..5118722fef5fb98edf5863588a5d6f1a932b1776"
+ "shas": "43ac69d0304e8f5a93bb985e3f4e05d9dff5d2b6..d7bd23e7679d4f3143995c6304e123585877638e"
}
,{
"testCaseDescription": "go-label-statements-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'insert_label' identifier in the main function of the 'main' module"
+ "summary": "Added the 'insert_label' identifier in the main function"
}
]
},
@@ -83,7 +98,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "5118722fef5fb98edf5863588a5d6f1a932b1776..86e5386c51e472b69c96dee0f11f13101ea549db"
+ "shas": "d7bd23e7679d4f3143995c6304e123585877638e..8114f172b2e02c45b8fd463e2091351fe761e226"
}
,{
"testCaseDescription": "go-label-statements-replacement-test",
@@ -115,7 +130,7 @@
}
]
},
- "summary": "Replaced the 'insert_label' identifier with the 'replacement_label' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'insert_label' identifier with the 'replacement_label' identifier in the main function"
}
]
},
@@ -139,7 +154,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "86e5386c51e472b69c96dee0f11f13101ea549db..5a05fa05c7fc5750b9b13926bc8c051100f8dbbf"
+ "shas": "8114f172b2e02c45b8fd463e2091351fe761e226..e7b09a82b9ebb4ceefce68cfefe69428b5f0a87c"
}
,{
"testCaseDescription": "go-label-statements-delete-replacement-test",
@@ -171,7 +186,7 @@
}
]
},
- "summary": "Replaced the 'replacement_label' identifier with the 'insert_label' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'replacement_label' identifier with the 'insert_label' identifier in the main function"
}
]
},
@@ -195,7 +210,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "5a05fa05c7fc5750b9b13926bc8c051100f8dbbf..0a064cd984a675ea6f57a157f4e410711dcef167"
+ "shas": "e7b09a82b9ebb4ceefce68cfefe69428b5f0a87c..876c876dba02766deea4ec644d0006c41d975f2f"
}
,{
"testCaseDescription": "go-label-statements-delete-insert-test",
@@ -215,7 +230,7 @@
]
}
},
- "summary": "Deleted the 'insert_label' identifier in the main function of the 'main' module"
+ "summary": "Deleted the 'insert_label' identifier in the main function"
}
]
},
@@ -240,7 +255,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "0a064cd984a675ea6f57a157f4e410711dcef167..84dde822378492f82447d8959a9978ab56a05ce7"
+ "shas": "876c876dba02766deea4ec644d0006c41d975f2f..3616fca3cc1bfdda36ba9e5a381194c409872b33"
}
,{
"testCaseDescription": "go-label-statements-teardown-test",
@@ -255,12 +270,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -282,5 +312,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "84dde822378492f82447d8959a9978ab56a05ce7..a759987355f2393c92a9df39d4c9e56a2ea2ce19"
+ "shas": "3616fca3cc1bfdda36ba9e5a381194c409872b33..030876029c6aa56a60b06740ec65bec788ad8715"
}]
diff --git a/test/corpus/diff-summaries/go/map-literals.json b/test/corpus/diff-summaries/go/map-literals.json
index f12a1c7cb..c7a2aa17c 100644
--- a/test/corpus/diff-summaries/go/map-literals.json
+++ b/test/corpus/diff-summaries/go/map-literals.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6e579109cc2a3c535790233b54306a5473f1a55d..842453c29866c4f8c23dffae58363865fdd48a9a"
+ "shas": "b8e41392436d04ec37de7c7358f5c6f016fc7726..9fc95fb47a671ca191c3f9160fa69e82af7dcaaa"
}
,{
"testCaseDescription": "go-map-literals-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 's' var assignment in the main function of the 'main' module"
+ "summary": "Added the 's' var assignment in the main function"
}
]
},
@@ -84,7 +99,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "842453c29866c4f8c23dffae58363865fdd48a9a..3386b91dd71edc5df18367f888ecc0e74380be0a"
+ "shas": "9fc95fb47a671ca191c3f9160fa69e82af7dcaaa..473f91f7465f2fc52a9fd4956332a44a981fe4cb"
}
,{
"testCaseDescription": "go-map-literals-replacement-test",
@@ -116,7 +131,7 @@
}
]
},
- "summary": "Replaced the 'string' identifier with the 'int' identifier in the map[string]int dictionary of the 'main' function"
+ "summary": "Replaced the 'string' identifier with the 'int' identifier in the map[string]int composite_literal of the 'main' function"
},
{
"span": {
@@ -131,7 +146,7 @@
]
}
},
- "summary": "Added the '\"foo\": \"bar\"' pair in the map[string]int dictionary of the 'main' function"
+ "summary": "Added the '\"foo\": \"bar\"' pair in the map[string]int composite_literal of the 'main' function"
},
{
"span": {
@@ -173,7 +188,7 @@
]
}
},
- "summary": "Deleted the '\"bye\": \"goodbye\"' pair in the map[string]int dictionary of the 'main' function"
+ "summary": "Deleted the '\"bye\": \"goodbye\"' pair in the map[string]int composite_literal of the 'main' function"
}
]
},
@@ -201,7 +216,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "3386b91dd71edc5df18367f888ecc0e74380be0a..b39961ba674aa0fab4180fe2cf44a1bfe0f1eb7c"
+ "shas": "473f91f7465f2fc52a9fd4956332a44a981fe4cb..0ae10bfe6756cfc5348f7d735b0e9fd248e5497f"
}
,{
"testCaseDescription": "go-map-literals-delete-replacement-test",
@@ -233,7 +248,7 @@
}
]
},
- "summary": "Replaced the 'int' identifier with the 'string' identifier in the map[string]string dictionary of the 'main' function"
+ "summary": "Replaced the 'int' identifier with the 'string' identifier in the map[string]string composite_literal of the 'main' function"
},
{
"span": {
@@ -369,7 +384,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b39961ba674aa0fab4180fe2cf44a1bfe0f1eb7c..148e204c29ec76ed54356dcc2ce2798967ea1dd0"
+ "shas": "0ae10bfe6756cfc5348f7d735b0e9fd248e5497f..dba7db8f0794b59b17c9a97ba84030fda238568d"
}
,{
"testCaseDescription": "go-map-literals-delete-insert-test",
@@ -389,7 +404,7 @@
]
}
},
- "summary": "Deleted the 's' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 's' var assignment in the main function"
}
]
},
@@ -415,7 +430,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "148e204c29ec76ed54356dcc2ce2798967ea1dd0..b42901f3f75330eff8ccf7342150ffc969e39861"
+ "shas": "dba7db8f0794b59b17c9a97ba84030fda238568d..d758ae59648d8fc240a1c58cc21f32703979e3cb"
}
,{
"testCaseDescription": "go-map-literals-teardown-test",
@@ -430,12 +445,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -457,5 +487,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b42901f3f75330eff8ccf7342150ffc969e39861..d8371152b551458e89b4e39819c41792bba80076"
+ "shas": "d758ae59648d8fc240a1c58cc21f32703979e3cb..0c8ae16482a04b19b4a23f3af01e4d9f314b712e"
}]
diff --git a/test/corpus/diff-summaries/go/map-types.json b/test/corpus/diff-summaries/go/map-types.json
index b7f37daa3..07dc74468 100644
--- a/test/corpus/diff-summaries/go/map-types.json
+++ b/test/corpus/diff-summaries/go/map-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "08a4feef4554fd83bb199f7d6aa2017f2d5dcf95..4490608b153d81227926e7fac6306bbbd15cd297"
+ "shas": "749bfb72d276ee57a9c014001d350bb1f642f2a9..4b873ee4062abb282e9203b75a1571d5a96f2ab6"
}
,{
"testCaseDescription": "go-map-types-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'm1' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'm1' type declaration in the main function"
}
]
},
@@ -81,7 +96,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "4490608b153d81227926e7fac6306bbbd15cd297..429d94f8628a073b8c3cb6694c09df6a2bf5a50c"
+ "shas": "4b873ee4062abb282e9203b75a1571d5a96f2ab6..b8f771d391d6de1c7d0c65c2f97c6086b2651fea"
}
,{
"testCaseDescription": "go-map-types-replacement-test",
@@ -136,7 +151,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "429d94f8628a073b8c3cb6694c09df6a2bf5a50c..64b519e321b5bb0774efbbfd0de8701be8cfc68d"
+ "shas": "b8f771d391d6de1c7d0c65c2f97c6086b2651fea..48ae3c021f6ff0f1870fc91f55ced9d0c767084f"
}
,{
"testCaseDescription": "go-map-types-delete-replacement-test",
@@ -191,7 +206,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "64b519e321b5bb0774efbbfd0de8701be8cfc68d..466082ac269bd4c15cd23acfabfcd6f667b3feb6"
+ "shas": "48ae3c021f6ff0f1870fc91f55ced9d0c767084f..941e1684bf0345854b50e36d415ca9ddc1bacd79"
}
,{
"testCaseDescription": "go-map-types-delete-insert-test",
@@ -211,7 +226,7 @@
]
}
},
- "summary": "Deleted the 'm1' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'm1' type declaration in the main function"
}
]
},
@@ -234,7 +249,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "466082ac269bd4c15cd23acfabfcd6f667b3feb6..a6fdcf70dd35754327a61460deefe9aa8d544f94"
+ "shas": "941e1684bf0345854b50e36d415ca9ddc1bacd79..2bdb5f2aec9d251005b91d9e6fa47e9d0ab273ad"
}
,{
"testCaseDescription": "go-map-types-teardown-test",
@@ -249,12 +264,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -276,5 +306,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a6fdcf70dd35754327a61460deefe9aa8d544f94..d2b5df75d8f6fa05372019f64a86177f47d3e2f6"
+ "shas": "2bdb5f2aec9d251005b91d9e6fa47e9d0ab273ad..4d24e891d2eff92e45db37ab2270eef8294e9145"
}]
diff --git a/test/corpus/diff-summaries/go/method-declarations.json b/test/corpus/diff-summaries/go/method-declarations.json
index 4c64334c3..7e732c64e 100644
--- a/test/corpus/diff-summaries/go/method-declarations.json
+++ b/test/corpus/diff-summaries/go/method-declarations.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+"
],
"gitDir": "test/corpus/repos/go",
- "shas": "2e4178577ebab07e2229a6846523de7a1a01d863..4236b968718153403eb7474c665ec2564c45d4af"
+ "shas": "a8adfaba3e02d1f9416a61ff929abbed0bc123d4..ae946e153675d03124e44ed3b708c539b9a137d7"
}
,{
"testCaseDescription": "go-method-declarations-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'Equals(…, …)' method in the main module"
+ "summary": "Added the 'Equals(…, …)' method"
}
]
},
@@ -80,7 +95,7 @@
"+func (self Person) Equals(other Person) bool {}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "4236b968718153403eb7474c665ec2564c45d4af..1be9a817b553812d204fbf84bdcdceeb09eda9aa"
+ "shas": "ae946e153675d03124e44ed3b708c539b9a137d7..f425e8a6f57e66d892e1f41ef0dbb8eead4b2df0"
}
,{
"testCaseDescription": "go-method-declarations-replacement-test",
@@ -112,7 +127,7 @@
}
]
},
- "summary": "Replaced the 'Person' identifier with the 'Num' identifier in the 'Equals(…, …)' method of the 'main' module"
+ "summary": "Replaced the 'Person' identifier with the 'Num' identifier in the 'Equals(…, …)' method"
},
{
"span": {
@@ -139,7 +154,7 @@
}
]
},
- "summary": "Replaced the 'Person' identifier with the 'Num' identifier in the 'Equals(…, …)' method of the 'main' module"
+ "summary": "Replaced the 'Person' identifier with the 'Num' identifier in the 'Equals(…, …)' method"
}
]
},
@@ -161,7 +176,7 @@
"+func (self Num) Equals(other Num) bool {}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "1be9a817b553812d204fbf84bdcdceeb09eda9aa..09e86485c7afef0d482a0f495713487f6af20df9"
+ "shas": "f425e8a6f57e66d892e1f41ef0dbb8eead4b2df0..8a314273a9e0b9e328c88a98232a005930d054e9"
}
,{
"testCaseDescription": "go-method-declarations-delete-replacement-test",
@@ -193,7 +208,7 @@
}
]
},
- "summary": "Replaced the 'Num' identifier with the 'Person' identifier in the 'Equals(…, …)' method of the 'main' module"
+ "summary": "Replaced the 'Num' identifier with the 'Person' identifier in the 'Equals(…, …)' method"
},
{
"span": {
@@ -220,7 +235,7 @@
}
]
},
- "summary": "Replaced the 'Num' identifier with the 'Person' identifier in the 'Equals(…, …)' method of the 'main' module"
+ "summary": "Replaced the 'Num' identifier with the 'Person' identifier in the 'Equals(…, …)' method"
}
]
},
@@ -242,7 +257,7 @@
"+func (self Person) Equals(other Person) bool {}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "09e86485c7afef0d482a0f495713487f6af20df9..4c2bf0fb4d489fa2924346c61f289cc66a591413"
+ "shas": "8a314273a9e0b9e328c88a98232a005930d054e9..65cf1134e9a92c0d5a1b4d6a160fcaf411f99806"
}
,{
"testCaseDescription": "go-method-declarations-delete-insert-test",
@@ -262,7 +277,7 @@
]
}
},
- "summary": "Deleted the 'Equals(…, …)' method in the main module"
+ "summary": "Deleted the 'Equals(…, …)' method"
}
]
},
@@ -284,7 +299,7 @@
"+"
],
"gitDir": "test/corpus/repos/go",
- "shas": "4c2bf0fb4d489fa2924346c61f289cc66a591413..7e9cc3775968f27c92b41ed9f4c8494fbcd30edc"
+ "shas": "65cf1134e9a92c0d5a1b4d6a160fcaf411f99806..516ad90702a68100aa6a68fc772bc05ef9d21161"
}
,{
"testCaseDescription": "go-method-declarations-teardown-test",
@@ -299,12 +314,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -326,5 +356,5 @@
"-"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7e9cc3775968f27c92b41ed9f4c8494fbcd30edc..7193c3cab8046a6b2b57792ecbef7f2ad5f318b7"
+ "shas": "516ad90702a68100aa6a68fc772bc05ef9d21161..407e4c1852d95bd8c9a3494899d65731e2bbb43f"
}]
diff --git a/test/corpus/diff-summaries/go/modifying-struct-fields.json b/test/corpus/diff-summaries/go/modifying-struct-fields.json
index c3fb1f0a2..38cdd6e48 100644
--- a/test/corpus/diff-summaries/go/modifying-struct-fields.json
+++ b/test/corpus/diff-summaries/go/modifying-struct-fields.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ab3e3926dc779249680c1d053599892d614e1cbf..7ece7fde5d7183a337db7501da3cfd85b9cf1ff2"
+ "shas": "f5a9b8a54a3841db93e420bf8eff96b4d2d6858a..94d93d2117a8e57a238a502919ff833d7cf671b9"
}
,{
"testCaseDescription": "go-modifying-struct-fields-insert-test",
@@ -52,13 +67,28 @@
4,
1
],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'ctx' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 8
+ ],
"end": [
6,
2
]
}
},
- "summary": "Added the 'ctx' var assignment in the main function of the 'main' module"
+ "summary": "Added the '&uploadContext{\n Remote: remote\n}' operator in the main function"
}
]
},
@@ -83,7 +113,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7ece7fde5d7183a337db7501da3cfd85b9cf1ff2..fe6d2e1a264c84287b55eaf223fd9c43c0de0b6a"
+ "shas": "94d93d2117a8e57a238a502919ff833d7cf671b9..a9aa97bd6ac93d93d8e62ca2a59b9ec861b684df"
}
,{
"testCaseDescription": "go-modifying-struct-fields-replacement-test",
@@ -115,7 +145,7 @@
}
]
},
- "summary": "Replaced the 'Remote: remote' pair with the 'trackedLocksMu: new(sync.Mutex)' pair in the ctx var assignment of the 'main' function"
+ "summary": "Replaced the 'Remote: remote' pair with the 'trackedLocksMu: new(sync.Mutex)' pair in the main function"
}
]
},
@@ -139,7 +169,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "fe6d2e1a264c84287b55eaf223fd9c43c0de0b6a..9d128deb722f6b1cc8daec493627470571d6aa22"
+ "shas": "a9aa97bd6ac93d93d8e62ca2a59b9ec861b684df..d0a359246dac8c80adcb1b4e7bac351462363d18"
}
,{
"testCaseDescription": "go-modifying-struct-fields-delete-replacement-test",
@@ -171,7 +201,7 @@
}
]
},
- "summary": "Replaced the 'trackedLocksMu: new(sync.Mutex)' pair with the 'Remote: remote' pair in the ctx var assignment of the 'main' function"
+ "summary": "Replaced the 'trackedLocksMu: new(sync.Mutex)' pair with the 'Remote: remote' pair in the main function"
}
]
},
@@ -195,7 +225,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9d128deb722f6b1cc8daec493627470571d6aa22..aae84499c2f50275110bf5576621b7d40d40f5fc"
+ "shas": "d0a359246dac8c80adcb1b4e7bac351462363d18..261a10edc770e3f40cd33d61dc0d61d0510527a5"
}
,{
"testCaseDescription": "go-modifying-struct-fields-delete-insert-test",
@@ -209,13 +239,28 @@
4,
1
],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'ctx' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 8
+ ],
"end": [
6,
2
]
}
},
- "summary": "Deleted the 'ctx' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the '&uploadContext{\n Remote: remote\n}' operator in the main function"
}
]
},
@@ -240,7 +285,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "aae84499c2f50275110bf5576621b7d40d40f5fc..785536c2045d588c9ac110cb6b5f084eba52ce59"
+ "shas": "261a10edc770e3f40cd33d61dc0d61d0510527a5..729241bd7988d5e569c4a3384c678328236ba019"
}
,{
"testCaseDescription": "go-modifying-struct-fields-teardown-test",
@@ -255,12 +300,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -282,5 +342,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "785536c2045d588c9ac110cb6b5f084eba52ce59..13e9de620f0e981a263aa8306692c8e3b7bae8a9"
+ "shas": "729241bd7988d5e569c4a3384c678328236ba019..b704517caf7ad227154e0582b74255cd4065e091"
}]
diff --git a/test/corpus/diff-summaries/go/parameter-declarations-with-types.json b/test/corpus/diff-summaries/go/parameter-declarations-with-types.json
index b30b4ecb3..1453c7c20 100644
--- a/test/corpus/diff-summaries/go/parameter-declarations-with-types.json
+++ b/test/corpus/diff-summaries/go/parameter-declarations-with-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 7,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -39,7 +54,7 @@
"+"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e8d08e2eedd6b2a25ec4649df0ad12534a6c3c09..adce0d5ed52ba8b1d7bca9e8a2bfb5364cda9502"
+ "shas": "57bf5ffc56480fbb108aa9d683b4dfd5324acbbf..86bd926b2066a8c508a3fbaea3aea1c44975dbaa"
}
,{
"testCaseDescription": "go-parameter-declarations-with-types-insert-test",
@@ -59,7 +74,7 @@
]
}
},
- "summary": "Added the 'foo' function in the main module"
+ "summary": "Added the 'foo' function"
}
]
},
@@ -82,7 +97,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "adce0d5ed52ba8b1d7bca9e8a2bfb5364cda9502..44490f03e295a0757ccab40c7b512e055e542679"
+ "shas": "86bd926b2066a8c508a3fbaea3aea1c44975dbaa..d06c9a9989b8b0b59b2ca2cdc1eae70936526a0b"
}
,{
"testCaseDescription": "go-parameter-declarations-with-types-replacement-test",
@@ -114,7 +129,7 @@
}
]
},
- "summary": "Replaced the 'int' identifier with the 'string' identifier in the foo function of the 'main' module"
+ "summary": "Replaced the 'int' identifier with the 'string' identifier in the foo function"
},
{
"span": {
@@ -141,7 +156,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'x' identifier in the foo function of the 'main' module"
+ "summary": "Replaced the 'a' identifier with the 'x' identifier in the foo function"
},
{
"span": {
@@ -168,7 +183,7 @@
}
]
},
- "summary": "Replaced the 'string' identifier with the 'uint64' identifier in the foo function of the 'main' module"
+ "summary": "Replaced the 'string' identifier with the 'uint64' identifier in the foo function"
},
{
"span": {
@@ -195,7 +210,7 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'y' identifier in the foo function of the 'main' module"
+ "summary": "Replaced the 'b' identifier with the 'y' identifier in the foo function"
}
]
},
@@ -218,7 +233,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "44490f03e295a0757ccab40c7b512e055e542679..e9a034ba8648ede7074592effb77584769908921"
+ "shas": "d06c9a9989b8b0b59b2ca2cdc1eae70936526a0b..7f7499916d8951812d1af4dc3f9edea6512dd4ae"
}
,{
"testCaseDescription": "go-parameter-declarations-with-types-delete-replacement-test",
@@ -238,7 +253,7 @@
]
}
},
- "summary": "Added the 'a int' parameter declaration in the foo function of the 'main' module"
+ "summary": "Added the 'a int' parameter declaration in the foo function"
},
{
"span": {
@@ -265,7 +280,7 @@
}
]
},
- "summary": "Replaced the 'x' identifier with the 'b' identifier in the foo function of the 'main' module"
+ "summary": "Replaced the 'x' identifier with the 'b' identifier in the foo function"
},
{
"span": {
@@ -280,7 +295,7 @@
]
}
},
- "summary": "Deleted the 'y uint64' parameter declaration in the foo function of the 'main' module"
+ "summary": "Deleted the 'y uint64' parameter declaration in the foo function"
}
]
},
@@ -303,7 +318,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e9a034ba8648ede7074592effb77584769908921..a62c254b900279d25d32867f50b43f29cf80e00f"
+ "shas": "7f7499916d8951812d1af4dc3f9edea6512dd4ae..84be95e6cce29e23fe13ac460c34d9d3639945c1"
}
,{
"testCaseDescription": "go-parameter-declarations-with-types-delete-insert-test",
@@ -323,7 +338,7 @@
]
}
},
- "summary": "Deleted the 'foo' function in the main module"
+ "summary": "Deleted the 'foo' function"
}
]
},
@@ -346,7 +361,7 @@
"+"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a62c254b900279d25d32867f50b43f29cf80e00f..9bc7d216469b8d8a278b807dca1cace07b3cffdc"
+ "shas": "84be95e6cce29e23fe13ac460c34d9d3639945c1..a396a786548a4d67126f0631959c0c1b53b66b84"
}
,{
"testCaseDescription": "go-parameter-declarations-with-types-teardown-test",
@@ -361,12 +376,27 @@
1
],
"end": [
- 7,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 4,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -389,5 +419,5 @@
"-"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9bc7d216469b8d8a278b807dca1cace07b3cffdc..d294ce5018da872a8921d3401c507217daf06328"
+ "shas": "a396a786548a4d67126f0631959c0c1b53b66b84..840ffcc3fb49c5769944cce7b4fc8f444c2b1aed"
}]
diff --git a/test/corpus/diff-summaries/go/pointer-types.json b/test/corpus/diff-summaries/go/pointer-types.json
index 8d998ac76..2e237a826 100644
--- a/test/corpus/diff-summaries/go/pointer-types.json
+++ b/test/corpus/diff-summaries/go/pointer-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d2b5df75d8f6fa05372019f64a86177f47d3e2f6..9731904c92acb4d04b65d34e08b9d71071dcdc9a"
+ "shas": "4d24e891d2eff92e45db37ab2270eef8294e9145..116be4b3120f1f63486563e681291568543040a1"
}
,{
"testCaseDescription": "go-pointer-types-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'p1' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'p1' type declaration in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'p2' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'p2' type declaration in the main function"
}
]
},
@@ -99,7 +114,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9731904c92acb4d04b65d34e08b9d71071dcdc9a..ed7d7ffc0969e8a9322c568c4b5691192fa53e29"
+ "shas": "116be4b3120f1f63486563e681291568543040a1..1d02b1285be95d48289fc2211acb0fa125211c7f"
}
,{
"testCaseDescription": "go-pointer-types-replacement-test",
@@ -184,7 +199,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ed7d7ffc0969e8a9322c568c4b5691192fa53e29..9c67261772de0af3f1d3a1daf03e9f2366d893c9"
+ "shas": "1d02b1285be95d48289fc2211acb0fa125211c7f..770917a4a293b42b5174083c47c9ff1fe396d74a"
}
,{
"testCaseDescription": "go-pointer-types-delete-replacement-test",
@@ -269,7 +284,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9c67261772de0af3f1d3a1daf03e9f2366d893c9..144a9aa0c6060fe481a5fd96f5bcdecfa3e3a4f1"
+ "shas": "770917a4a293b42b5174083c47c9ff1fe396d74a..44240e8fb91d10af8d97d7680ae5e314f1b9488b"
}
,{
"testCaseDescription": "go-pointer-types-delete-insert-test",
@@ -289,7 +304,7 @@
]
}
},
- "summary": "Deleted the 'p1' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'p1' type declaration in the main function"
},
{
"span": {
@@ -304,7 +319,7 @@
]
}
},
- "summary": "Deleted the 'p2' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'p2' type declaration in the main function"
}
]
},
@@ -330,7 +345,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "144a9aa0c6060fe481a5fd96f5bcdecfa3e3a4f1..4070351f018be548cadfc29137148e78bcab00d9"
+ "shas": "44240e8fb91d10af8d97d7680ae5e314f1b9488b..5d1dc64c31a4ecafee88706bb1cdda5eb1656f76"
}
,{
"testCaseDescription": "go-pointer-types-teardown-test",
@@ -345,12 +360,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -372,5 +402,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "4070351f018be548cadfc29137148e78bcab00d9..ffe628ad363e676d5234caa95a87cf6b7f3626f8"
+ "shas": "5d1dc64c31a4ecafee88706bb1cdda5eb1656f76..8ae798e3c9773e3d5b6af35228d06445dd50426f"
}]
diff --git a/test/corpus/diff-summaries/go/qualified-types.json b/test/corpus/diff-summaries/go/qualified-types.json
index a2ac17fe8..a7aec5445 100644
--- a/test/corpus/diff-summaries/go/qualified-types.json
+++ b/test/corpus/diff-summaries/go/qualified-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9b6482e7bca1a74c6ecdc400cf0ed146ebb6a29a..3b06e2854335bedd951acd5f610a193a8950ba8d"
+ "shas": "e86ae4b80ecf2b01260ea4afc56327253ab59646..0b24fa2e9250263fe1f145381ac2c399f2bc23a3"
}
,{
"testCaseDescription": "go-qualified-types-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'a' type declaration in the main function"
}
]
},
@@ -81,7 +96,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "3b06e2854335bedd951acd5f610a193a8950ba8d..fa461b7018b844b35433dc120e6e9d5eb5ee403e"
+ "shas": "0b24fa2e9250263fe1f145381ac2c399f2bc23a3..126af8d1df2c5faeb2893ac84505890ebe324198"
}
,{
"testCaseDescription": "go-qualified-types-replacement-test",
@@ -163,7 +178,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "fa461b7018b844b35433dc120e6e9d5eb5ee403e..98c0500dc82c4fbe24656621178b4815b96fdfc9"
+ "shas": "126af8d1df2c5faeb2893ac84505890ebe324198..b27f53d7ebab5cff17b7faca0c11a5af4393a993"
}
,{
"testCaseDescription": "go-qualified-types-delete-replacement-test",
@@ -245,7 +260,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "98c0500dc82c4fbe24656621178b4815b96fdfc9..b282ee0787fec70acb2eb0e3902092f4e9947f79"
+ "shas": "b27f53d7ebab5cff17b7faca0c11a5af4393a993..f349dcabe71c3355438e8c08830ed229a427dbce"
}
,{
"testCaseDescription": "go-qualified-types-delete-insert-test",
@@ -265,7 +280,7 @@
]
}
},
- "summary": "Deleted the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'a' type declaration in the main function"
}
]
},
@@ -288,7 +303,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b282ee0787fec70acb2eb0e3902092f4e9947f79..846ee6590bfa7e86f523096b8a876a557732af95"
+ "shas": "f349dcabe71c3355438e8c08830ed229a427dbce..138ffc1319221b4f305f24212159aea75438ec8f"
}
,{
"testCaseDescription": "go-qualified-types-teardown-test",
@@ -303,12 +318,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -330,5 +360,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "846ee6590bfa7e86f523096b8a876a557732af95..2a8d9f01f7c78b4014cc0cf0057b991673c39dd0"
+ "shas": "138ffc1319221b4f305f24212159aea75438ec8f..26a0f67120f1cf6fc8e13694d29195177fe1040e"
}]
diff --git a/test/corpus/diff-summaries/go/rune-literals.json b/test/corpus/diff-summaries/go/rune-literals.json
index 8710c145d..957288adc 100644
--- a/test/corpus/diff-summaries/go/rune-literals.json
+++ b/test/corpus/diff-summaries/go/rune-literals.json
@@ -11,8 +11,8 @@
1
],
"end": [
- 3,
- 1
+ 1,
+ 13
]
}
},
@@ -35,7 +35,7 @@
"+"
],
"gitDir": "test/corpus/repos/go",
- "shas": "39b5a7d4eaa477c3d1636e32ab2c5cf5c930372a..23dc2a672c4cc4345fe894e56e3d0db174dec0a9"
+ "shas": "663f0278d8c41aca54ae0d1849efc76213f9ba1f..1e54211c4612f5a3f6fddae7d3c3eae18327a9cd"
}
,{
"testCaseDescription": "go-rune-literals-insert-test",
@@ -55,7 +55,7 @@
]
}
},
- "summary": "Added the 'a' var assignment in the main module"
+ "summary": "Added the 'a' var assignment"
},
{
"span": {
@@ -70,7 +70,7 @@
]
}
},
- "summary": "Added the 'b' var assignment in the main module"
+ "summary": "Added the 'b' var assignment"
},
{
"span": {
@@ -85,7 +85,7 @@
]
}
},
- "summary": "Added the 'c' var assignment in the main module"
+ "summary": "Added the 'c' var assignment"
},
{
"span": {
@@ -100,7 +100,7 @@
]
}
},
- "summary": "Added the 'd' var assignment in the main module"
+ "summary": "Added the 'd' var assignment"
},
{
"span": {
@@ -115,8 +115,12 @@
]
}
},
- "summary": "Added the 'e' var assignment in the main module"
- },
+ "summary": "Added the 'e' var assignment"
+ }
+ ]
+ },
+ "errors": {
+ "rune-literals.go": [
{
"span": {
"insert": {
@@ -124,62 +128,16 @@
8,
3
],
- "end": [
- 8,
- 4
- ]
- }
- },
- "summary": "Added the 'f' identifier in the main module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 7
- ],
- "end": [
- 8,
- 9
- ]
- }
- },
- "summary": "Added the ''⌘' error in the main module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 9
- ],
- "end": [
- 8,
- 13
- ]
- }
- },
- "summary": "Added the 'jjjj' identifier in the main module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 13
- ],
"end": [
9,
1
]
}
},
- "summary": "Added the ''\n' error in the main module"
+ "summary": "Added 'f = '⌘jjjj'\n' at line 8, column 3 - line 9, column 1"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"rune-literals.go"
@@ -202,7 +160,7 @@
"+)"
],
"gitDir": "test/corpus/repos/go",
- "shas": "23dc2a672c4cc4345fe894e56e3d0db174dec0a9..7aed7c8739c2eac0863eacaf994d8eabdce7cb1d"
+ "shas": "1e54211c4612f5a3f6fddae7d3c3eae18327a9cd..7946dc95b2a2eaa4a44da409ed54a82a54ed188a"
}
,{
"testCaseDescription": "go-rune-literals-replacement-test",
@@ -234,7 +192,7 @@
}
]
},
- "summary": "Replaced the ''δ'' rune literal with the ''©'' rune literal in the a var assignment of the 'main' module"
+ "summary": "Replaced the ''δ'' rune literal with the ''©'' rune literal in the a var assignment"
},
{
"span": {
@@ -261,7 +219,7 @@
}
]
},
- "summary": "Replaced the ''⌘'' rune literal with the ''©'' rune literal in the b var assignment of the 'main' module"
+ "summary": "Replaced the ''⌘'' rune literal with the ''©'' rune literal in the b var assignment"
},
{
"span": {
@@ -288,7 +246,7 @@
}
]
},
- "summary": "Replaced the ''⌘'' rune literal with the ''©'' rune literal in the c var assignment of the 'main' module"
+ "summary": "Replaced the ''⌘'' rune literal with the ''©'' rune literal in the c var assignment"
},
{
"span": {
@@ -315,7 +273,7 @@
}
]
},
- "summary": "Replaced the ''⌘'' rune literal with the ''©'' rune literal in the d var assignment of the 'main' module"
+ "summary": "Replaced the ''⌘'' rune literal with the ''©'' rune literal in the d var assignment"
},
{
"span": {
@@ -342,7 +300,7 @@
}
]
},
- "summary": "Replaced the ''⌘'' rune literal with the ''©'' rune literal in the e var assignment of the 'main' module"
+ "summary": "Replaced the ''⌘'' rune literal with the ''©'' rune literal in the e var assignment"
},
{
"span": {
@@ -357,8 +315,12 @@
]
}
},
- "summary": "Added the 'f' var assignment in the main module"
- },
+ "summary": "Added the 'f' var assignment"
+ }
+ ]
+ },
+ "errors": {
+ "rune-literals.go": [
{
"span": {
"delete": {
@@ -366,62 +328,16 @@
8,
3
],
- "end": [
- 8,
- 4
- ]
- }
- },
- "summary": "Deleted the 'f' identifier in the main module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 7
- ],
- "end": [
- 8,
- 9
- ]
- }
- },
- "summary": "Deleted the ''⌘' error in the main module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 9
- ],
- "end": [
- 8,
- 13
- ]
- }
- },
- "summary": "Deleted the 'jjjj' identifier in the main module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 13
- ],
"end": [
9,
1
]
}
},
- "summary": "Deleted the ''\n' error in the main module"
+ "summary": "Deleted 'f = '⌘jjjj'\n' at line 8, column 3 - line 9, column 1"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"rune-literals.go"
@@ -449,7 +365,7 @@
" )"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7aed7c8739c2eac0863eacaf994d8eabdce7cb1d..ec461a8fd869ec7d76f4fd58bc588149153f716f"
+ "shas": "7946dc95b2a2eaa4a44da409ed54a82a54ed188a..9846819cac6a3814f8fc03011b6e0c38af042214"
}
,{
"testCaseDescription": "go-rune-literals-delete-replacement-test",
@@ -481,7 +397,7 @@
}
]
},
- "summary": "Replaced the ''©'' rune literal with the ''δ'' rune literal in the a var assignment of the 'main' module"
+ "summary": "Replaced the ''©'' rune literal with the ''δ'' rune literal in the a var assignment"
},
{
"span": {
@@ -508,7 +424,7 @@
}
]
},
- "summary": "Replaced the ''©'' rune literal with the ''⌘'' rune literal in the b var assignment of the 'main' module"
+ "summary": "Replaced the ''©'' rune literal with the ''⌘'' rune literal in the b var assignment"
},
{
"span": {
@@ -535,7 +451,7 @@
}
]
},
- "summary": "Replaced the ''©'' rune literal with the ''⌘'' rune literal in the c var assignment of the 'main' module"
+ "summary": "Replaced the ''©'' rune literal with the ''⌘'' rune literal in the c var assignment"
},
{
"span": {
@@ -562,7 +478,7 @@
}
]
},
- "summary": "Replaced the ''©'' rune literal with the ''⌘'' rune literal in the d var assignment of the 'main' module"
+ "summary": "Replaced the ''©'' rune literal with the ''⌘'' rune literal in the d var assignment"
},
{
"span": {
@@ -589,67 +505,7 @@
}
]
},
- "summary": "Replaced the ''©'' rune literal with the ''⌘'' rune literal in the e var assignment of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 3
- ],
- "end": [
- 8,
- 4
- ]
- }
- },
- "summary": "Added the 'f' identifier in the main module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 7
- ],
- "end": [
- 8,
- 9
- ]
- }
- },
- "summary": "Added the ''⌘' error in the main module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 9
- ],
- "end": [
- 8,
- 13
- ]
- }
- },
- "summary": "Added the 'jjjj' identifier in the main module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 8,
- 13
- ],
- "end": [
- 9,
- 1
- ]
- }
- },
- "summary": "Added the ''\n' error in the main module"
+ "summary": "Replaced the ''©'' rune literal with the ''⌘'' rune literal in the e var assignment"
},
{
"span": {
@@ -664,11 +520,29 @@
]
}
},
- "summary": "Deleted the 'f' var assignment in the main module"
+ "summary": "Deleted the 'f' var assignment"
}
]
},
- "errors": {}
+ "errors": {
+ "rune-literals.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 8,
+ 3
+ ],
+ "end": [
+ 9,
+ 1
+ ]
+ }
+ },
+ "summary": "Added 'f = '⌘jjjj'\n' at line 8, column 3 - line 9, column 1"
+ }
+ ]
+ }
},
"filePaths": [
"rune-literals.go"
@@ -696,7 +570,7 @@
" )"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ec461a8fd869ec7d76f4fd58bc588149153f716f..9993f655e33779241cf9c1eac0effb677eab220e"
+ "shas": "9846819cac6a3814f8fc03011b6e0c38af042214..cc35d6332ea1c0dc789bfa7f461eba04824cf783"
}
,{
"testCaseDescription": "go-rune-literals-delete-insert-test",
@@ -716,7 +590,7 @@
]
}
},
- "summary": "Deleted the 'a' var assignment in the main module"
+ "summary": "Deleted the 'a' var assignment"
},
{
"span": {
@@ -731,7 +605,7 @@
]
}
},
- "summary": "Deleted the 'b' var assignment in the main module"
+ "summary": "Deleted the 'b' var assignment"
},
{
"span": {
@@ -746,7 +620,7 @@
]
}
},
- "summary": "Deleted the 'c' var assignment in the main module"
+ "summary": "Deleted the 'c' var assignment"
},
{
"span": {
@@ -761,7 +635,7 @@
]
}
},
- "summary": "Deleted the 'd' var assignment in the main module"
+ "summary": "Deleted the 'd' var assignment"
},
{
"span": {
@@ -776,8 +650,12 @@
]
}
},
- "summary": "Deleted the 'e' var assignment in the main module"
- },
+ "summary": "Deleted the 'e' var assignment"
+ }
+ ]
+ },
+ "errors": {
+ "rune-literals.go": [
{
"span": {
"delete": {
@@ -785,62 +663,16 @@
8,
3
],
- "end": [
- 8,
- 4
- ]
- }
- },
- "summary": "Deleted the 'f' identifier in the main module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 7
- ],
- "end": [
- 8,
- 9
- ]
- }
- },
- "summary": "Deleted the ''⌘' error in the main module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 9
- ],
- "end": [
- 8,
- 13
- ]
- }
- },
- "summary": "Deleted the 'jjjj' identifier in the main module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 8,
- 13
- ],
"end": [
9,
1
]
}
},
- "summary": "Deleted the ''\n' error in the main module"
+ "summary": "Deleted 'f = '⌘jjjj'\n' at line 8, column 3 - line 9, column 1"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"rune-literals.go"
@@ -863,7 +695,7 @@
"+"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9993f655e33779241cf9c1eac0effb677eab220e..36a9483d64f31ef89f73f8aee014ca4a1dfc4d58"
+ "shas": "cc35d6332ea1c0dc789bfa7f461eba04824cf783..1cc444aa94d7784497f5d15ca15b1569b467732d"
}
,{
"testCaseDescription": "go-rune-literals-teardown-test",
@@ -878,8 +710,8 @@
1
],
"end": [
- 3,
- 1
+ 1,
+ 13
]
}
},
@@ -902,5 +734,5 @@
"-"
],
"gitDir": "test/corpus/repos/go",
- "shas": "36a9483d64f31ef89f73f8aee014ca4a1dfc4d58..a43f5210e8e5da594371eacab324e27889547ce0"
+ "shas": "1cc444aa94d7784497f5d15ca15b1569b467732d..fd41bb91afdd6087f0c3e6c54566857b7105df8c"
}]
diff --git a/test/corpus/diff-summaries/go/select-statements.json b/test/corpus/diff-summaries/go/select-statements.json
index b1065077d..2ee7b4aee 100644
--- a/test/corpus/diff-summaries/go/select-statements.json
+++ b/test/corpus/diff-summaries/go/select-statements.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a5c82828c92a590f5a64d58dd4a626b294a2c565..931059c522f5de3c9c26c635a0d8309c5a15b163"
+ "shas": "cb913819d62f34c2cc72aa293b39fabca1a0f05c..16284699449cfa8d9ebef6df6c39765b1952a1f5"
}
,{
"testCaseDescription": "go-select-statements-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added a select statement in the main function of the 'main' module"
+ "summary": "Added a select statement in the main function"
}
]
},
@@ -90,7 +105,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "931059c522f5de3c9c26c635a0d8309c5a15b163..783bd292c6edd57dbeecda21a7fa4779dd7df37e"
+ "shas": "16284699449cfa8d9ebef6df6c39765b1952a1f5..d72bb50ec9a41c5cad553f3a0d9dfb889749dee1"
}
,{
"testCaseDescription": "go-select-statements-replacement-test",
@@ -122,7 +137,7 @@
}
]
},
- "summary": "Replaced the 'x' identifier with the 'a' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'x' identifier with the 'a' identifier in the main function"
},
{
"span": {
@@ -149,7 +164,7 @@
}
]
},
- "summary": "Replaced the 'y' identifier with the 'b' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'y' identifier with the 'b' identifier in the main function"
},
{
"span": {
@@ -207,7 +222,7 @@
" return"
],
"gitDir": "test/corpus/repos/go",
- "shas": "783bd292c6edd57dbeecda21a7fa4779dd7df37e..f41ff4cddf48a52a085d1342eb0f99089f143658"
+ "shas": "d72bb50ec9a41c5cad553f3a0d9dfb889749dee1..6556fe84b67435f6c768377975c181a125a5a9f1"
}
,{
"testCaseDescription": "go-select-statements-delete-replacement-test",
@@ -239,7 +254,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'x' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'a' identifier with the 'x' identifier in the main function"
},
{
"span": {
@@ -266,7 +281,7 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'y' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'b' identifier with the 'y' identifier in the main function"
},
{
"span": {
@@ -324,7 +339,7 @@
" return"
],
"gitDir": "test/corpus/repos/go",
- "shas": "f41ff4cddf48a52a085d1342eb0f99089f143658..cccdfbcb5e7e96a105a3dc63051bd47d7f2a518e"
+ "shas": "6556fe84b67435f6c768377975c181a125a5a9f1..3882dca1074e6564bc01f79a1b44f2c0db17d3e2"
}
,{
"testCaseDescription": "go-select-statements-delete-insert-test",
@@ -344,7 +359,7 @@
]
}
},
- "summary": "Deleted a select statement in the main function of the 'main' module"
+ "summary": "Deleted a select statement in the main function"
}
]
},
@@ -376,7 +391,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "cccdfbcb5e7e96a105a3dc63051bd47d7f2a518e..016dfc524f2334477842e78c5c8e0d9a63760013"
+ "shas": "3882dca1074e6564bc01f79a1b44f2c0db17d3e2..51576f63dc98b44fbb1042065c9ab828a27dd5f7"
}
,{
"testCaseDescription": "go-select-statements-teardown-test",
@@ -391,12 +406,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -418,5 +448,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "016dfc524f2334477842e78c5c8e0d9a63760013..8ae829c0b1cf177164c31d8a3d6678bbc51d20c5"
+ "shas": "51576f63dc98b44fbb1042065c9ab828a27dd5f7..fa9acd974705290312a7cebdba09b18008dc6093"
}]
diff --git a/test/corpus/diff-summaries/go/selector-expressions.json b/test/corpus/diff-summaries/go/selector-expressions.json
index af06150d7..569ced868 100644
--- a/test/corpus/diff-summaries/go/selector-expressions.json
+++ b/test/corpus/diff-summaries/go/selector-expressions.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "92abc0a7c86e4fde9374babdb2efcd398d27f6ac..d801e97024f83d9e1877e12a313446d798b56cc8"
+ "shas": "eca7c6083f4f3169ebc3bf726c3d936818a2d174..aeb74c519ca8d7d63e6d35cff856d277c571b6f7"
}
,{
"testCaseDescription": "go-selector-expressions-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a[b][c]()' function call in the main function of the 'main' module"
+ "summary": "Added the 'a[b][c]()' function call in the main function"
}
]
},
@@ -81,7 +96,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d801e97024f83d9e1877e12a313446d798b56cc8..ea2eeeacd1bd254d9b113e7743aca93de78e20c4"
+ "shas": "aeb74c519ca8d7d63e6d35cff856d277c571b6f7..a59ce1e7d20b1843f9b59495e1a6b3f7d8c096f4"
}
,{
"testCaseDescription": "go-selector-expressions-replacement-test",
@@ -190,7 +205,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ea2eeeacd1bd254d9b113e7743aca93de78e20c4..5f3a65a2146a6f53f7898a59138cd7eff5ba13a7"
+ "shas": "a59ce1e7d20b1843f9b59495e1a6b3f7d8c096f4..9c0b77724a8c467d16ad46f5f184144b65216512"
}
,{
"testCaseDescription": "go-selector-expressions-delete-replacement-test",
@@ -299,7 +314,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "5f3a65a2146a6f53f7898a59138cd7eff5ba13a7..c5794aa359e1f8866d3de42d8dc71b730f6cddec"
+ "shas": "9c0b77724a8c467d16ad46f5f184144b65216512..a2f408b126df5e135832ae9d566dab50031792ec"
}
,{
"testCaseDescription": "go-selector-expressions-delete-insert-test",
@@ -319,7 +334,7 @@
]
}
},
- "summary": "Deleted the 'a[b][c]()' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'a[b][c]()' function call in the main function"
}
]
},
@@ -342,7 +357,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c5794aa359e1f8866d3de42d8dc71b730f6cddec..166ba5c0c7069627f7f405f4b1b0e88c638f6cd8"
+ "shas": "a2f408b126df5e135832ae9d566dab50031792ec..7ee0dab9d8d593cbca3c6230313f3eaeda0ada55"
}
,{
"testCaseDescription": "go-selector-expressions-teardown-test",
@@ -357,12 +372,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -384,5 +414,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "166ba5c0c7069627f7f405f4b1b0e88c638f6cd8..54cc2c98c56816e321a4fffb6927c2793f3cc794"
+ "shas": "7ee0dab9d8d593cbca3c6230313f3eaeda0ada55..0a55a88480be2cc766ee756b5b5f7bf45704376c"
}]
diff --git a/test/corpus/diff-summaries/go/send-statements.json b/test/corpus/diff-summaries/go/send-statements.json
index ed004e1f0..e5e679bd6 100644
--- a/test/corpus/diff-summaries/go/send-statements.json
+++ b/test/corpus/diff-summaries/go/send-statements.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "80bb1d299fa3720eb3cdcef8c428f696467572a8..ba6c9f47972e2a5d648603c09f723d009d6e8d18"
+ "shas": "1d4f678537c1a2636fd9eba370de9e81de874c72..9ff735e947d0cc8440903c7acee54ccd8de2cbc1"
}
,{
"testCaseDescription": "go-send-statements-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'foo <- 5' send statement in the main function of the 'main' module"
+ "summary": "Added the 'foo <- 5' send statement in the main function"
}
]
},
@@ -81,7 +96,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ba6c9f47972e2a5d648603c09f723d009d6e8d18..c42ab69df8aec76fe7bf0ca080bf1f79dd2b676e"
+ "shas": "9ff735e947d0cc8440903c7acee54ccd8de2cbc1..8fc0429afe1c5062f256e0423bf7f7dae8e0b1e2"
}
,{
"testCaseDescription": "go-send-statements-replacement-test",
@@ -113,7 +128,7 @@
}
]
},
- "summary": "Replaced the 'foo' identifier with the 'bar' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'foo' identifier with the 'bar' identifier in the main function"
},
{
"span": {
@@ -140,7 +155,7 @@
}
]
},
- "summary": "Replaced '5' with '6' in the main function of the 'main' module"
+ "summary": "Replaced '5' with '6' in the main function"
}
]
},
@@ -163,7 +178,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c42ab69df8aec76fe7bf0ca080bf1f79dd2b676e..a3e71dbd1f3ef1035d929f31add8b1fa600d972d"
+ "shas": "8fc0429afe1c5062f256e0423bf7f7dae8e0b1e2..54cd41da0c7bb8d56aa5e7cd6f0903908c8e321b"
}
,{
"testCaseDescription": "go-send-statements-delete-replacement-test",
@@ -195,7 +210,7 @@
}
]
},
- "summary": "Replaced the 'bar' identifier with the 'foo' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'bar' identifier with the 'foo' identifier in the main function"
},
{
"span": {
@@ -222,7 +237,7 @@
}
]
},
- "summary": "Replaced '6' with '5' in the main function of the 'main' module"
+ "summary": "Replaced '6' with '5' in the main function"
}
]
},
@@ -245,7 +260,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a3e71dbd1f3ef1035d929f31add8b1fa600d972d..7c616dcf9e47d1a400931f274ccc02c3b73079bf"
+ "shas": "54cd41da0c7bb8d56aa5e7cd6f0903908c8e321b..3a2b37c02821a9daa3416c419f1efbad8ecb1ce4"
}
,{
"testCaseDescription": "go-send-statements-delete-insert-test",
@@ -265,7 +280,7 @@
]
}
},
- "summary": "Deleted the 'foo <- 5' send statement in the main function of the 'main' module"
+ "summary": "Deleted the 'foo <- 5' send statement in the main function"
}
]
},
@@ -288,7 +303,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7c616dcf9e47d1a400931f274ccc02c3b73079bf..fa350bf0e3bd5e40724cf87b2fe792b32420ac11"
+ "shas": "3a2b37c02821a9daa3416c419f1efbad8ecb1ce4..4be86e6bc27ab2ed64363e832a3291202eecc707"
}
,{
"testCaseDescription": "go-send-statements-teardown-test",
@@ -303,12 +318,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -330,5 +360,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "fa350bf0e3bd5e40724cf87b2fe792b32420ac11..adb2401da7e74b66c885cf959788358c7ba5c3ee"
+ "shas": "4be86e6bc27ab2ed64363e832a3291202eecc707..bb4ba3185a52b92f422411ad6cae97a82e2b2657"
}]
diff --git a/test/corpus/diff-summaries/go/short-var-declarations.json b/test/corpus/diff-summaries/go/short-var-declarations.json
index e4bcc090f..c45523ac0 100644
--- a/test/corpus/diff-summaries/go/short-var-declarations.json
+++ b/test/corpus/diff-summaries/go/short-var-declarations.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b534a2624a6f74eebed7bd6da21bc7df27018a96..a338438394d4abed73faf1a18db50b9ce7fd5d05"
+ "shas": "e3c2411f013b063d1c440d3a295be6485170c63d..3f76dd06eb1d09789402bf6941a8d177785db15d"
}
,{
"testCaseDescription": "go-short-var-declarations-insert-test",
@@ -54,18 +69,48 @@
],
"end": [
4,
- 13
+ 2
]
}
},
- "summary": "Added the 'a' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'a' identifier in the main function"
},
{
"span": {
"insert": {
"start": [
4,
- 1
+ 4
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 9
+ ],
+ "end": [
+ 4,
+ 10
+ ]
+ }
+ },
+ "summary": "Added '1' in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 12
],
"end": [
4,
@@ -73,7 +118,7 @@
]
}
},
- "summary": "Added the 'b' var assignment in the main function of the 'main' module"
+ "summary": "Added '2' in the main function"
}
]
},
@@ -96,7 +141,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a338438394d4abed73faf1a18db50b9ce7fd5d05..1e403ac766aab96d8b2aaabca728c1ed81699dc5"
+ "shas": "3f76dd06eb1d09789402bf6941a8d177785db15d..187c1b52a8ed9334d34195fc341535c8d021c0d4"
}
,{
"testCaseDescription": "go-short-var-declarations-replacement-test",
@@ -128,34 +173,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'x' identifier in the x var assignment of the 'main' function"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
- 9
- ],
- "end": [
- 4,
- 10
- ]
- },
- {
- "start": [
- 4,
- 9
- ],
- "end": [
- 4,
- 10
- ]
- }
- ]
- },
- "summary": "Replaced '1' with '3' in the x var assignment of the 'main' function"
+ "summary": "Replaced the 'a' identifier with the 'x' identifier in the main function"
},
{
"span": {
@@ -182,7 +200,34 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'y' identifier in the y var assignment of the 'main' function"
+ "summary": "Replaced the 'b' identifier with the 'y' identifier in the main function"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 4,
+ 9
+ ],
+ "end": [
+ 4,
+ 10
+ ]
+ },
+ {
+ "start": [
+ 4,
+ 9
+ ],
+ "end": [
+ 4,
+ 10
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced '1' with '3' in the main function"
},
{
"span": {
@@ -209,7 +254,7 @@
}
]
},
- "summary": "Replaced '2' with '4' in the y var assignment of the 'main' function"
+ "summary": "Replaced '2' with '4' in the main function"
}
]
},
@@ -232,7 +277,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "1e403ac766aab96d8b2aaabca728c1ed81699dc5..e31233f516ea4df97b36bffc70f140f6af79caa3"
+ "shas": "187c1b52a8ed9334d34195fc341535c8d021c0d4..cb1ef5208e3c762f6d149a56bea8c42e448e8ef0"
}
,{
"testCaseDescription": "go-short-var-declarations-delete-replacement-test",
@@ -264,34 +309,7 @@
}
]
},
- "summary": "Replaced the 'x' identifier with the 'a' identifier in the a var assignment of the 'main' function"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 4,
- 9
- ],
- "end": [
- 4,
- 10
- ]
- },
- {
- "start": [
- 4,
- 9
- ],
- "end": [
- 4,
- 10
- ]
- }
- ]
- },
- "summary": "Replaced '3' with '1' in the a var assignment of the 'main' function"
+ "summary": "Replaced the 'x' identifier with the 'a' identifier in the main function"
},
{
"span": {
@@ -318,7 +336,34 @@
}
]
},
- "summary": "Replaced the 'y' identifier with the 'b' identifier in the b var assignment of the 'main' function"
+ "summary": "Replaced the 'y' identifier with the 'b' identifier in the main function"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 4,
+ 9
+ ],
+ "end": [
+ 4,
+ 10
+ ]
+ },
+ {
+ "start": [
+ 4,
+ 9
+ ],
+ "end": [
+ 4,
+ 10
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced '3' with '1' in the main function"
},
{
"span": {
@@ -345,7 +390,7 @@
}
]
},
- "summary": "Replaced '4' with '2' in the b var assignment of the 'main' function"
+ "summary": "Replaced '4' with '2' in the main function"
}
]
},
@@ -368,7 +413,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e31233f516ea4df97b36bffc70f140f6af79caa3..fe209f5ee06cef0653f60cd08571fd635a66b457"
+ "shas": "cb1ef5208e3c762f6d149a56bea8c42e448e8ef0..d7c2a9a102abb7226275c4d464907a4154b782c3"
}
,{
"testCaseDescription": "go-short-var-declarations-delete-insert-test",
@@ -384,18 +429,48 @@
],
"end": [
4,
- 13
+ 2
]
}
},
- "summary": "Deleted the 'a' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'a' identifier in the main function"
},
{
"span": {
"delete": {
"start": [
4,
- 1
+ 4
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 9
+ ],
+ "end": [
+ 4,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted '1' in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 12
],
"end": [
4,
@@ -403,7 +478,7 @@
]
}
},
- "summary": "Deleted the 'b' var assignment in the main function of the 'main' module"
+ "summary": "Deleted '2' in the main function"
}
]
},
@@ -426,7 +501,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "fe209f5ee06cef0653f60cd08571fd635a66b457..c57c2196ef90d21ae6ecd07593b7e224ce45f1f2"
+ "shas": "d7c2a9a102abb7226275c4d464907a4154b782c3..716f05adcb3b0c9c3fcd7166f770fe32c639d348"
}
,{
"testCaseDescription": "go-short-var-declarations-teardown-test",
@@ -441,12 +516,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -468,5 +558,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c57c2196ef90d21ae6ecd07593b7e224ce45f1f2..47074688bbb73b3e4bf4fe48f221e411e5a9dcae"
+ "shas": "716f05adcb3b0c9c3fcd7166f770fe32c639d348..d5f8f49ab00e91cf9cf8a71dd94c14b3fa29aad8"
}]
diff --git a/test/corpus/diff-summaries/go/single-import-declarations.json b/test/corpus/diff-summaries/go/single-import-declarations.json
index a9c7ea3e3..645dd4609 100644
--- a/test/corpus/diff-summaries/go/single-import-declarations.json
+++ b/test/corpus/diff-summaries/go/single-import-declarations.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,28 +53,13 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "f4187df470bc7a1989964a210ecab051ffbf6ee6..ecb901a6762362605dadbdffaf473d73e6b94df5"
+ "shas": "6de9ab15bd1a30f31bd2fdd3fefaef8985e7de52..7fefb122c064688a8968f969eac26609be94d94f"
}
,{
"testCaseDescription": "go-single-import-declarations-insert-test",
"expectedResult": {
"changes": {
"single-import-declarations.go": [
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 7
- ]
- }
- },
- "summary": "Added the 'import' identifier in the main function of the 'main' module"
- },
{
"span": {
"insert": {
@@ -73,22 +73,7 @@
]
}
},
- "summary": "Added the \"net/http\" string in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 1
- ],
- "end": [
- 5,
- 7
- ]
- }
- },
- "summary": "Added the 'import' identifier in the main function of the 'main' module"
+ "summary": "Added the \"net/http\" string in the main function"
},
{
"span": {
@@ -103,7 +88,7 @@
]
}
},
- "summary": "Added the \"some/dsl\" string in the main function of the 'main' module"
+ "summary": "Added the \"some/dsl\" string in the main function"
},
{
"span": {
@@ -118,7 +103,41 @@
]
}
},
- "summary": "Added the 'import' identifier in the main function of the 'main' module"
+ "summary": "Added the 'import' identifier in the main function"
+ }
+ ]
+ },
+ "errors": {
+ "single-import-declarations.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 7
+ ]
+ }
+ },
+ "summary": "Added 'import' at line 4, column 1 - line 4, column 7 in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 9
+ ]
+ }
+ },
+ "summary": "Added 'import .' at line 5, column 1 - line 5, column 9 in the main function"
},
{
"span": {
@@ -127,32 +146,16 @@
6,
8
],
- "end": [
- 6,
- 13
- ]
- }
- },
- "summary": "Added the 'alias' identifier in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 6,
- 14
- ],
"end": [
6,
28
]
}
},
- "summary": "Added the \"some/package\" string in the main function of the 'main' module"
+ "summary": "Added 'alias \"some/package\"' at line 6, column 8 - line 6, column 28 in the main function"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"single-import-declarations.go"
@@ -173,7 +176,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ecb901a6762362605dadbdffaf473d73e6b94df5..c0a1539d6ec6fcae30b6d51910d103da40611255"
+ "shas": "7fefb122c064688a8968f969eac26609be94d94f..6dae7ceccb9cb8e85281d1a4c1d8c5d8c661255c"
}
,{
"testCaseDescription": "go-single-import-declarations-replacement-test",
@@ -205,7 +208,7 @@
}
]
},
- "summary": "Replaced the \"net/http\" string with the \"foo/bar\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"net/http\" string with the \"foo/bar\" string in the main function"
},
{
"span": {
@@ -232,7 +235,7 @@
}
]
},
- "summary": "Replaced the \"some/dsl\" string with the \"types/dsl\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"some/dsl\" string with the \"types/dsl\" string in the main function"
},
{
"span": {
@@ -259,7 +262,7 @@
}
]
},
- "summary": "Replaced the \"some/package\" string with the \"awesome/packages\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"some/package\" string with the \"awesome/packages\" string in the main function"
}
]
},
@@ -286,7 +289,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c0a1539d6ec6fcae30b6d51910d103da40611255..9969e0e7578020fd9e352796aaed70ff7c363470"
+ "shas": "6dae7ceccb9cb8e85281d1a4c1d8c5d8c661255c..ae5e4f4a6a921e1170a9b85ae3b090f15172be85"
}
,{
"testCaseDescription": "go-single-import-declarations-delete-replacement-test",
@@ -318,7 +321,7 @@
}
]
},
- "summary": "Replaced the \"foo/bar\" string with the \"net/http\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"foo/bar\" string with the \"net/http\" string in the main function"
},
{
"span": {
@@ -345,7 +348,7 @@
}
]
},
- "summary": "Replaced the \"types/dsl\" string with the \"some/dsl\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"types/dsl\" string with the \"some/dsl\" string in the main function"
},
{
"span": {
@@ -372,7 +375,7 @@
}
]
},
- "summary": "Replaced the \"awesome/packages\" string with the \"some/package\" string in the main function of the 'main' module"
+ "summary": "Replaced the \"awesome/packages\" string with the \"some/package\" string in the main function"
}
]
},
@@ -399,28 +402,13 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9969e0e7578020fd9e352796aaed70ff7c363470..c27faf90add827958f33afdb42e202228554d956"
+ "shas": "ae5e4f4a6a921e1170a9b85ae3b090f15172be85..be9944b647c93dcdb02ce3d892d04a35c1bd7f52"
}
,{
"testCaseDescription": "go-single-import-declarations-delete-insert-test",
"expectedResult": {
"changes": {
"single-import-declarations.go": [
- {
- "span": {
- "delete": {
- "start": [
- 4,
- 1
- ],
- "end": [
- 4,
- 7
- ]
- }
- },
- "summary": "Deleted the 'import' identifier in the main function of the 'main' module"
- },
{
"span": {
"delete": {
@@ -434,22 +422,7 @@
]
}
},
- "summary": "Deleted the \"net/http\" string in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 1
- ],
- "end": [
- 5,
- 7
- ]
- }
- },
- "summary": "Deleted the 'import' identifier in the main function of the 'main' module"
+ "summary": "Deleted the \"net/http\" string in the main function"
},
{
"span": {
@@ -464,7 +437,7 @@
]
}
},
- "summary": "Deleted the \"some/dsl\" string in the main function of the 'main' module"
+ "summary": "Deleted the \"some/dsl\" string in the main function"
},
{
"span": {
@@ -479,7 +452,41 @@
]
}
},
- "summary": "Deleted the 'import' identifier in the main function of the 'main' module"
+ "summary": "Deleted the 'import' identifier in the main function"
+ }
+ ]
+ },
+ "errors": {
+ "single-import-declarations.go": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted 'import' at line 4, column 1 - line 4, column 7 in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted 'import .' at line 5, column 1 - line 5, column 9 in the main function"
},
{
"span": {
@@ -488,32 +495,16 @@
6,
8
],
- "end": [
- 6,
- 13
- ]
- }
- },
- "summary": "Deleted the 'alias' identifier in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 6,
- 14
- ],
"end": [
6,
28
]
}
},
- "summary": "Deleted the \"some/package\" string in the main function of the 'main' module"
+ "summary": "Deleted 'alias \"some/package\"' at line 6, column 8 - line 6, column 28 in the main function"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"single-import-declarations.go"
@@ -534,7 +525,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c27faf90add827958f33afdb42e202228554d956..eb482cb703294d1f5cd117ad9c0a350463a0eb28"
+ "shas": "be9944b647c93dcdb02ce3d892d04a35c1bd7f52..d091a3255b8271e218572299738095d3efe19115"
}
,{
"testCaseDescription": "go-single-import-declarations-teardown-test",
@@ -549,12 +540,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -576,5 +582,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "eb482cb703294d1f5cd117ad9c0a350463a0eb28..2c47fd719e136db59fa2b3ccfab4572fe4c1be2c"
+ "shas": "d091a3255b8271e218572299738095d3efe19115..126db53cee9459e0927b80ed1af574cc273f948e"
}]
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 55ad7c7bb..dfb319d78 100644
--- a/test/corpus/diff-summaries/go/single-line-function-declarations.json
+++ b/test/corpus/diff-summaries/go/single-line-function-declarations.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,28 +53,13 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e5224329c24b2e2d564a10269e63b36c492d7bf5..3312d6a7e5ab88bd23a6abafd432862a90f72e77"
+ "shas": "7ebca2c2e26873ec2ec3d92c6922446eb95bb61f..cfc5ed7d21deace3c8eabd9d394e916da7e41a46"
}
,{
"testCaseDescription": "go-single-line-function-declarations-insert-test",
"expectedResult": {
"changes": {
"single-line-function-declarations.go": [
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 6
- ],
- "end": [
- 4,
- 10
- ]
- }
- },
- "summary": "Added the 'f1()' function call in the main function of the 'main' module"
- },
{
"span": {
"insert": {
@@ -73,22 +73,7 @@
]
}
},
- "summary": "Added the 'a()' function call in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 10
- ]
- }
- },
- "summary": "Added the 'f2()' function call in the main function of the 'main' module"
+ "summary": "Added the 'a()' function call in the main function"
},
{
"span": {
@@ -103,7 +88,7 @@
]
}
},
- "summary": "Added the 'a()' function call in the main function of the 'main' module"
+ "summary": "Added the 'a()' function call in the main function"
},
{
"span": {
@@ -118,22 +103,7 @@
]
}
},
- "summary": "Added the 'b()' function call in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 6,
- 6
- ],
- "end": [
- 6,
- 10
- ]
- }
- },
- "summary": "Added the 'f3()' function call in the main function of the 'main' module"
+ "summary": "Added the 'b()' function call in the main function"
},
{
"span": {
@@ -148,7 +118,7 @@
]
}
},
- "summary": "Added the 'a()' function call in the main function of the 'main' module"
+ "summary": "Added the 'a()' function call in the main function"
},
{
"span": {
@@ -163,11 +133,59 @@
]
}
},
- "summary": "Added the 'b()' function call in the main function of the 'main' module"
+ "summary": "Added the 'b()' function call in the main function"
}
]
},
- "errors": {}
+ "errors": {
+ "single-line-function-declarations.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 10
+ ]
+ }
+ },
+ "summary": "Added 'func f1()' at line 4, column 1 - line 4, column 10 in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 10
+ ]
+ }
+ },
+ "summary": "Added 'func f2()' at line 5, column 1 - line 5, column 10 in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 10
+ ]
+ }
+ },
+ "summary": "Added 'func f3()' at line 6, column 1 - line 6, column 10 in the main function"
+ }
+ ]
+ }
},
"filePaths": [
"single-line-function-declarations.go"
@@ -188,7 +206,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "3312d6a7e5ab88bd23a6abafd432862a90f72e77..3b4e43cd88706feb3352b0d5cb5b3a31cc71995f"
+ "shas": "cfc5ed7d21deace3c8eabd9d394e916da7e41a46..978bbef12122d7954da3d7f7dfa67cfea28a84f9"
}
,{
"testCaseDescription": "go-single-line-function-declarations-replacement-test",
@@ -222,36 +240,6 @@
},
"summary": "Replaced the 'f1' identifier with the 'g1' identifier in the g1() function call of the 'main' function"
},
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 10
- ]
- }
- },
- "summary": "Added the 'g2()' function call in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 10
- ]
- }
- },
- "summary": "Deleted the 'f2()' function call in the main function of the 'main' module"
- },
{
"span": {
"replace": [
@@ -281,7 +269,40 @@
}
]
},
- "errors": {}
+ "errors": {
+ "single-line-function-declarations.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 10
+ ]
+ }
+ },
+ "summary": "Added 'func g2()' at line 5, column 1 - line 5, column 10 in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted 'func f2()' at line 5, column 1 - line 5, column 10 in the main function"
+ }
+ ]
+ }
},
"filePaths": [
"single-line-function-declarations.go"
@@ -304,7 +325,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "3b4e43cd88706feb3352b0d5cb5b3a31cc71995f..e5af3487fd74f8e7848f798682e4e440cae6b7c6"
+ "shas": "978bbef12122d7954da3d7f7dfa67cfea28a84f9..2896a28ff80236db618c50ceb2b9d9469a4ea425"
}
,{
"testCaseDescription": "go-single-line-function-declarations-delete-replacement-test",
@@ -338,36 +359,6 @@
},
"summary": "Replaced the 'g1' identifier with the 'f1' identifier in the f1() function call of the 'main' function"
},
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 10
- ]
- }
- },
- "summary": "Added the 'f2()' function call in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 10
- ]
- }
- },
- "summary": "Deleted the 'g2()' function call in the main function of the 'main' module"
- },
{
"span": {
"replace": [
@@ -397,7 +388,40 @@
}
]
},
- "errors": {}
+ "errors": {
+ "single-line-function-declarations.go": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 10
+ ]
+ }
+ },
+ "summary": "Added 'func f2()' at line 5, column 1 - line 5, column 10 in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted 'func g2()' at line 5, column 1 - line 5, column 10 in the main function"
+ }
+ ]
+ }
},
"filePaths": [
"single-line-function-declarations.go"
@@ -420,28 +444,13 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e5af3487fd74f8e7848f798682e4e440cae6b7c6..bac460f21956d6e7fe9ab2ef377e0815765c16b7"
+ "shas": "2896a28ff80236db618c50ceb2b9d9469a4ea425..94b20a0aaf7aef755357df422b0f96413e3532f9"
}
,{
"testCaseDescription": "go-single-line-function-declarations-delete-insert-test",
"expectedResult": {
"changes": {
"single-line-function-declarations.go": [
- {
- "span": {
- "delete": {
- "start": [
- 4,
- 6
- ],
- "end": [
- 4,
- 10
- ]
- }
- },
- "summary": "Deleted the 'f1()' function call in the main function of the 'main' module"
- },
{
"span": {
"delete": {
@@ -455,22 +464,7 @@
]
}
},
- "summary": "Deleted the 'a()' function call in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 10
- ]
- }
- },
- "summary": "Deleted the 'f2()' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'a()' function call in the main function"
},
{
"span": {
@@ -485,7 +479,7 @@
]
}
},
- "summary": "Deleted the 'a()' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'a()' function call in the main function"
},
{
"span": {
@@ -500,22 +494,7 @@
]
}
},
- "summary": "Deleted the 'b()' function call in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 6,
- 6
- ],
- "end": [
- 6,
- 10
- ]
- }
- },
- "summary": "Deleted the 'f3()' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'b()' function call in the main function"
},
{
"span": {
@@ -530,7 +509,7 @@
]
}
},
- "summary": "Deleted the 'a()' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'a()' function call in the main function"
},
{
"span": {
@@ -545,11 +524,59 @@
]
}
},
- "summary": "Deleted the 'b()' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'b()' function call in the main function"
}
]
},
- "errors": {}
+ "errors": {
+ "single-line-function-declarations.go": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted 'func f1()' at line 4, column 1 - line 4, column 10 in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 5,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted 'func f2()' at line 5, column 1 - line 5, column 10 in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 6,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted 'func f3()' at line 6, column 1 - line 6, column 10 in the main function"
+ }
+ ]
+ }
},
"filePaths": [
"single-line-function-declarations.go"
@@ -570,7 +597,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "bac460f21956d6e7fe9ab2ef377e0815765c16b7..ced62ce15d64d383929a5e60c092f3fccef6beb2"
+ "shas": "94b20a0aaf7aef755357df422b0f96413e3532f9..911d3b87f28310cf84bd22c59757753c61dca6c4"
}
,{
"testCaseDescription": "go-single-line-function-declarations-teardown-test",
@@ -585,12 +612,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -612,5 +654,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ced62ce15d64d383929a5e60c092f3fccef6beb2..6eefcab8de06ce411a43f0fe718199942aa7d74b"
+ "shas": "911d3b87f28310cf84bd22c59757753c61dca6c4..aa75d831de9909c8ed71c01ca49d0b4ef4e4b7e8"
}]
diff --git a/test/corpus/diff-summaries/go/slice-literals.json b/test/corpus/diff-summaries/go/slice-literals.json
index d9e3d9a55..8d656b07e 100644
--- a/test/corpus/diff-summaries/go/slice-literals.json
+++ b/test/corpus/diff-summaries/go/slice-literals.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7f89178b8db506e68863bdca31d6ed7b5ef34432..9cbed93dd18fb5a433067f07af286fc91e37d580"
+ "shas": "8db0bd957201afac84d98da63dd95cb8e725c256..0b90f2526d52190d9afeab0e9f7f22fe14c94394"
}
,{
"testCaseDescription": "go-slice-literals-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 's1' var assignment in the main function of the 'main' module"
+ "summary": "Added the 's1' var assignment in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 's2' var assignment in the main function of the 'main' module"
+ "summary": "Added the 's2' var assignment in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 's3' var assignment in the main function of the 'main' module"
+ "summary": "Added the 's3' var assignment in the main function"
}
]
},
@@ -116,7 +131,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9cbed93dd18fb5a433067f07af286fc91e37d580..2d2bda48aedbb35ebadaacf82ace9b0df85a4f4a"
+ "shas": "0b90f2526d52190d9afeab0e9f7f22fe14c94394..d2ab6b2a6bc827f778accd158152671516e7148b"
}
,{
"testCaseDescription": "go-slice-literals-replacement-test",
@@ -148,7 +163,7 @@
}
]
},
- "summary": "Replaced the '{}' literal with the \"sup\" string in the []string{\"sup\"} slice literal of the 'main' function"
+ "summary": "Replaced the '{}' literal with the \"sup\" string in the []string\"sup\" composite_literal of the 'main' function"
},
{
"span": {
@@ -175,7 +190,7 @@
}
]
},
- "summary": "Replaced the \"hi\" string with the \"hello\" string in the []string{\"hello\"} slice literal of the 'main' function"
+ "summary": "Replaced the \"hi\" string with the \"hello\" string in the []string\"hello\" composite_literal of the 'main' function"
},
{
"span": {
@@ -202,7 +217,7 @@
}
]
},
- "summary": "Replaced the \"hi\" string with the \"bar\" string in the []string{\n\"bar\",\n \"baz\",\n} slice literal of the 'main' function"
+ "summary": "Replaced the \"hi\" string with the \"bar\" string in the []string\"bar\", \"baz\" composite_literal of the 'main' function"
},
{
"span": {
@@ -229,7 +244,7 @@
}
]
},
- "summary": "Replaced the \"hello\" string with the \"baz\" string in the []string{\n\"bar\",\n \"baz\",\n} slice literal of the 'main' function"
+ "summary": "Replaced the \"hello\" string with the \"baz\" string in the []string\"bar\", \"baz\" composite_literal of the 'main' function"
}
]
},
@@ -260,7 +275,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "2d2bda48aedbb35ebadaacf82ace9b0df85a4f4a..7fbf589cc2afd7e04cfe40ea0a43f595d29c315f"
+ "shas": "d2ab6b2a6bc827f778accd158152671516e7148b..1df5ade839691a6de61d73b255d3c09de62f6bba"
}
,{
"testCaseDescription": "go-slice-literals-delete-replacement-test",
@@ -292,7 +307,7 @@
}
]
},
- "summary": "Replaced the \"sup\" string with the '{}' literal in the []string{} slice literal of the 'main' function"
+ "summary": "Replaced the \"sup\" string with the '{}' literal in the []string{} composite_literal of the 'main' function"
},
{
"span": {
@@ -319,7 +334,7 @@
}
]
},
- "summary": "Replaced the \"hello\" string with the \"hi\" string in the []string{\"hi\"} slice literal of the 'main' function"
+ "summary": "Replaced the \"hello\" string with the \"hi\" string in the []string\"hi\" composite_literal of the 'main' function"
},
{
"span": {
@@ -346,7 +361,7 @@
}
]
},
- "summary": "Replaced the \"bar\" string with the \"hi\" string in the []string{\n\"hi\",\n \"hello\",\n} slice literal of the 'main' function"
+ "summary": "Replaced the \"bar\" string with the \"hi\" string in the []string\"hi\", \"hello\" composite_literal of the 'main' function"
},
{
"span": {
@@ -373,7 +388,7 @@
}
]
},
- "summary": "Replaced the \"baz\" string with the \"hello\" string in the []string{\n\"hi\",\n \"hello\",\n} slice literal of the 'main' function"
+ "summary": "Replaced the \"baz\" string with the \"hello\" string in the []string\"hi\", \"hello\" composite_literal of the 'main' function"
}
]
},
@@ -404,7 +419,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7fbf589cc2afd7e04cfe40ea0a43f595d29c315f..82f42fdce01229819499fe0259f515475b325643"
+ "shas": "1df5ade839691a6de61d73b255d3c09de62f6bba..d772b054e12dc6500aa60b00277272b757caa6ac"
}
,{
"testCaseDescription": "go-slice-literals-delete-insert-test",
@@ -424,7 +439,7 @@
]
}
},
- "summary": "Deleted the 's1' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 's1' var assignment in the main function"
},
{
"span": {
@@ -439,7 +454,7 @@
]
}
},
- "summary": "Deleted the 's2' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 's2' var assignment in the main function"
},
{
"span": {
@@ -454,7 +469,7 @@
]
}
},
- "summary": "Deleted the 's3' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 's3' var assignment in the main function"
}
]
},
@@ -482,7 +497,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "82f42fdce01229819499fe0259f515475b325643..e2beb2e207d48d0916488297474e7ebc528a9ebb"
+ "shas": "d772b054e12dc6500aa60b00277272b757caa6ac..fb7e33bba45e0fce349cadac8b7fb638c9446dff"
}
,{
"testCaseDescription": "go-slice-literals-teardown-test",
@@ -497,12 +512,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -524,5 +554,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e2beb2e207d48d0916488297474e7ebc528a9ebb..ce81a7d517fc9a2808b223f5e2ec2b77fd6fad64"
+ "shas": "fb7e33bba45e0fce349cadac8b7fb638c9446dff..576026694b333d8935d7a3e88a32dbd0ed0b3fa4"
}]
diff --git a/test/corpus/diff-summaries/go/slice-types.json b/test/corpus/diff-summaries/go/slice-types.json
index 5af453b4c..99f25f3c5 100644
--- a/test/corpus/diff-summaries/go/slice-types.json
+++ b/test/corpus/diff-summaries/go/slice-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "50b59edcf73e7686cbfc6db242bf00346aebcf11..d6310fb2cb6a3013e2b74fbb86ad3747cbc8c3b0"
+ "shas": "242b339cd8dd07d6f1232ff7f96ee2eb324516d9..5b4731f5adac70903edeb633e9e21dd24b5786e4"
}
,{
"testCaseDescription": "go-slice-types-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'a' type declaration in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'c' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'c' type declaration in the main function"
}
]
},
@@ -97,7 +112,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d6310fb2cb6a3013e2b74fbb86ad3747cbc8c3b0..28aecb53c4b8319c2ccc461e4dcda828d54e2519"
+ "shas": "5b4731f5adac70903edeb633e9e21dd24b5786e4..c9b289da486a64d171721252d096cfe151f30a18"
}
,{
"testCaseDescription": "go-slice-types-replacement-test",
@@ -187,7 +202,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "28aecb53c4b8319c2ccc461e4dcda828d54e2519..7c99446920a5d7a179e4ad80f488390954ac9926"
+ "shas": "c9b289da486a64d171721252d096cfe151f30a18..fe1225e665ec5b7b147bf09bd6692c8092e4e4e2"
}
,{
"testCaseDescription": "go-slice-types-delete-replacement-test",
@@ -277,7 +292,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7c99446920a5d7a179e4ad80f488390954ac9926..b3d602bfbf09eaebab6252dbafa11cf16eea486a"
+ "shas": "fe1225e665ec5b7b147bf09bd6692c8092e4e4e2..270d41af2f2a6046963eceed150f5d08ea1c986f"
}
,{
"testCaseDescription": "go-slice-types-delete-insert-test",
@@ -297,7 +312,7 @@
]
}
},
- "summary": "Deleted the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'a' type declaration in the main function"
},
{
"span": {
@@ -312,7 +327,7 @@
]
}
},
- "summary": "Deleted the 'c' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'c' type declaration in the main function"
}
]
},
@@ -336,7 +351,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b3d602bfbf09eaebab6252dbafa11cf16eea486a..c56ff2e3361eee55cbbe9c7f88a4b98bc660603b"
+ "shas": "270d41af2f2a6046963eceed150f5d08ea1c986f..d16cbfb0816b433e10a58e6ba96499e390853933"
}
,{
"testCaseDescription": "go-slice-types-teardown-test",
@@ -351,12 +366,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -378,5 +408,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c56ff2e3361eee55cbbe9c7f88a4b98bc660603b..e7ced9b59ed0acd00138211528dda1ac5c7c084a"
+ "shas": "d16cbfb0816b433e10a58e6ba96499e390853933..57665a31ef098c76a33d7fb8dc14586054888e70"
}]
diff --git a/test/corpus/diff-summaries/go/string-literals.json b/test/corpus/diff-summaries/go/string-literals.json
index 75fdf7d4c..da764c725 100644
--- a/test/corpus/diff-summaries/go/string-literals.json
+++ b/test/corpus/diff-summaries/go/string-literals.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "1ed63b35351e352f6ae6a546bb49920585747c54..c56cc611221c01bb9287c12f7a140673e10ab90d"
+ "shas": "d39cc6bcd81255864bc210bd0ab92a71c0a80cc2..16d9a34f668dbafe6dbdfac745ffc44545f4bd9e"
}
,{
"testCaseDescription": "go-string-literals-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'a' var assignment in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'b' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'b' var assignment in the main function"
}
]
},
@@ -99,7 +114,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c56cc611221c01bb9287c12f7a140673e10ab90d..5c98f182bc937bb033e29f8fba6b4815154c9ddf"
+ "shas": "16d9a34f668dbafe6dbdfac745ffc44545f4bd9e..5619d5dc5d1278e4363419d4f9c02a729726fc39"
}
,{
"testCaseDescription": "go-string-literals-replacement-test",
@@ -184,7 +199,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "5c98f182bc937bb033e29f8fba6b4815154c9ddf..625fbd81d426bac45985add4c251aef9b07bdb9a"
+ "shas": "5619d5dc5d1278e4363419d4f9c02a729726fc39..c4aa7c20e6d9a2950d7db2be45b980ddd7e99ce8"
}
,{
"testCaseDescription": "go-string-literals-delete-replacement-test",
@@ -269,7 +284,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "625fbd81d426bac45985add4c251aef9b07bdb9a..fb189b28aeac87b0e47f67f9cd4fcff3f5025568"
+ "shas": "c4aa7c20e6d9a2950d7db2be45b980ddd7e99ce8..e4a86bf76b1bf8a7419a94a59780b272876d53c1"
}
,{
"testCaseDescription": "go-string-literals-delete-insert-test",
@@ -289,7 +304,7 @@
]
}
},
- "summary": "Deleted the 'a' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'a' var assignment in the main function"
},
{
"span": {
@@ -304,7 +319,7 @@
]
}
},
- "summary": "Deleted the 'b' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'b' var assignment in the main function"
}
]
},
@@ -330,7 +345,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "fb189b28aeac87b0e47f67f9cd4fcff3f5025568..6b98b0bc60654ce90e6f87db94145bc968e516b6"
+ "shas": "e4a86bf76b1bf8a7419a94a59780b272876d53c1..40eb9809170e085cc42ac58d979fca5b61d14679"
}
,{
"testCaseDescription": "go-string-literals-teardown-test",
@@ -345,12 +360,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -372,5 +402,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6b98b0bc60654ce90e6f87db94145bc968e516b6..7f89178b8db506e68863bdca31d6ed7b5ef34432"
+ "shas": "40eb9809170e085cc42ac58d979fca5b61d14679..8db0bd957201afac84d98da63dd95cb8e725c256"
}]
diff --git a/test/corpus/diff-summaries/go/struct-field-declarations.json b/test/corpus/diff-summaries/go/struct-field-declarations.json
index 3847b3d6f..510c468ed 100644
--- a/test/corpus/diff-summaries/go/struct-field-declarations.json
+++ b/test/corpus/diff-summaries/go/struct-field-declarations.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "965eb67a3019ef8aea91e5f5a3975bd6c27ddbd5..9ee5a9f77efee88839be792650cb42006c9944db"
+ "shas": "65bbc171b8f70b289f47abe480d261056b5ea251..2d2f04046fa3f3d412aa2637b4291e67833048c7"
}
,{
"testCaseDescription": "go-struct-field-declarations-insert-test",
@@ -83,7 +98,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9ee5a9f77efee88839be792650cb42006c9944db..dc61e6a712517a5a39433d0e53b63273a01d6fbb"
+ "shas": "2d2f04046fa3f3d412aa2637b4291e67833048c7..fff65061ac778ebd7eea2950833f8a0a715ef39f"
}
,{
"testCaseDescription": "go-struct-field-declarations-replacement-test",
@@ -110,12 +125,12 @@
],
"end": [
5,
- 11
+ 4
]
}
]
},
- "summary": "Replaced the 'g int' field declaration with the 'h, i int' field declaration in the struct {\n h, i int\n} struct type of the 'main' function"
+ "summary": "Replaced the 'g int' field declaration with the 'h' identifier in the struct {\n h, i int\n} struct type of the 'main' function"
}
]
},
@@ -139,7 +154,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "dc61e6a712517a5a39433d0e53b63273a01d6fbb..50cb546cb19607f9c8a093b477ac5d44274dff8d"
+ "shas": "fff65061ac778ebd7eea2950833f8a0a715ef39f..68b3cf1b72905aa30e13bcc35e0c6f644e90898a"
}
,{
"testCaseDescription": "go-struct-field-declarations-delete-replacement-test",
@@ -156,7 +171,7 @@
],
"end": [
5,
- 11
+ 4
]
},
{
@@ -171,7 +186,7 @@
}
]
},
- "summary": "Replaced the 'h, i int' field declaration with the 'g int' field declaration in the struct {\n g int\n} struct type of the 'main' function"
+ "summary": "Replaced the 'h' identifier with the 'g int' field declaration in the struct {\n g int\n} struct type of the 'main' function"
}
]
},
@@ -195,7 +210,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "50cb546cb19607f9c8a093b477ac5d44274dff8d..9c7b8ddb39b33db0564ba9e22a6e6802e14ad008"
+ "shas": "68b3cf1b72905aa30e13bcc35e0c6f644e90898a..278c27a97dbee140d6467c09af4c6c835c6eca6e"
}
,{
"testCaseDescription": "go-struct-field-declarations-delete-insert-test",
@@ -240,7 +255,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9c7b8ddb39b33db0564ba9e22a6e6802e14ad008..38cf3544fbd1e1cfb3b4aa39964fce74939ef046"
+ "shas": "278c27a97dbee140d6467c09af4c6c835c6eca6e..e8d2d6f98417cadd0f0706b362a004e24387f31a"
}
,{
"testCaseDescription": "go-struct-field-declarations-teardown-test",
@@ -255,12 +270,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -282,5 +312,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "38cf3544fbd1e1cfb3b4aa39964fce74939ef046..d6bf5b852da48acbbdc8d627de9e645d28d7f38d"
+ "shas": "e8d2d6f98417cadd0f0706b362a004e24387f31a..67d576bfc545aeab08b6970a41866b4643831ec5"
}]
diff --git a/test/corpus/diff-summaries/go/struct-literals.json b/test/corpus/diff-summaries/go/struct-literals.json
index 935915549..46dd9f368 100644
--- a/test/corpus/diff-summaries/go/struct-literals.json
+++ b/test/corpus/diff-summaries/go/struct-literals.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d8371152b551458e89b4e39819c41792bba80076..96eafb3baf0354f59b4e4ead7603dcb9a8c610c9"
+ "shas": "0c8ae16482a04b19b4a23f3af01e4d9f314b712e..1f15b0d1afbb74572f14840fe6bf05c90fc968d8"
}
,{
"testCaseDescription": "go-struct-literals-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 's1' var assignment in the main function of the 'main' module"
+ "summary": "Added the 's1' var assignment in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 's2' var assignment in the main function of the 'main' module"
+ "summary": "Added the 's2' var assignment in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 's3' var assignment in the main function of the 'main' module"
+ "summary": "Added the 's3' var assignment in the main function"
}
]
},
@@ -116,7 +131,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "96eafb3baf0354f59b4e4ead7603dcb9a8c610c9..787d8b0d4326b990ca39ecfa787d21dacfce56ea"
+ "shas": "1f15b0d1afbb74572f14840fe6bf05c90fc968d8..4494c26fb9999b04a2c61cf39c32d1d24e8d5f8d"
}
,{
"testCaseDescription": "go-struct-literals-replacement-test",
@@ -286,7 +301,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "787d8b0d4326b990ca39ecfa787d21dacfce56ea..b1e1747bfe7b356b150181c65accb131af2adc1a"
+ "shas": "4494c26fb9999b04a2c61cf39c32d1d24e8d5f8d..206d1a39d3694158ecdad426673ec76d48e374af"
}
,{
"testCaseDescription": "go-struct-literals-delete-replacement-test",
@@ -456,7 +471,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b1e1747bfe7b356b150181c65accb131af2adc1a..9062d2928c093b9470596646a5802e7375970a2e"
+ "shas": "206d1a39d3694158ecdad426673ec76d48e374af..021bb0b55e32d2b017f2b4b29dddcd790cea242d"
}
,{
"testCaseDescription": "go-struct-literals-delete-insert-test",
@@ -476,7 +491,7 @@
]
}
},
- "summary": "Deleted the 's1' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 's1' var assignment in the main function"
},
{
"span": {
@@ -491,7 +506,7 @@
]
}
},
- "summary": "Deleted the 's2' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 's2' var assignment in the main function"
},
{
"span": {
@@ -506,7 +521,7 @@
]
}
},
- "summary": "Deleted the 's3' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 's3' var assignment in the main function"
}
]
},
@@ -534,7 +549,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9062d2928c093b9470596646a5802e7375970a2e..e3dccb9f0e80e1d4dd95ad8f77fc1f3d70da1c56"
+ "shas": "021bb0b55e32d2b017f2b4b29dddcd790cea242d..dc132533bd95c31a8f5e9bb4b9a62e2feb4c10f6"
}
,{
"testCaseDescription": "go-struct-literals-teardown-test",
@@ -549,12 +564,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -576,5 +606,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e3dccb9f0e80e1d4dd95ad8f77fc1f3d70da1c56..80bb1d299fa3720eb3cdcef8c428f696467572a8"
+ "shas": "dc132533bd95c31a8f5e9bb4b9a62e2feb4c10f6..1d4f678537c1a2636fd9eba370de9e81de874c72"
}]
diff --git a/test/corpus/diff-summaries/go/struct-types.json b/test/corpus/diff-summaries/go/struct-types.json
index 0c95c086d..cb35c7a13 100644
--- a/test/corpus/diff-summaries/go/struct-types.json
+++ b/test/corpus/diff-summaries/go/struct-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e7ced9b59ed0acd00138211528dda1ac5c7c084a..b52397c136bdd9b41868a929f0d416ee1c6abf97"
+ "shas": "57665a31ef098c76a33d7fb8dc14586054888e70..3660aaf9358df40375f73cb4bfb377a1382b7d3e"
}
,{
"testCaseDescription": "go-struct-types-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 's1' type declaration in the main function of the 'main' module"
+ "summary": "Added the 's1' type declaration in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 's2' type declaration in the main function of the 'main' module"
+ "summary": "Added the 's2' type declaration in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 's3' type declaration in the main function of the 'main' module"
+ "summary": "Added the 's3' type declaration in the main function"
},
{
"span": {
@@ -103,7 +118,7 @@
]
}
},
- "summary": "Added the 's4' type declaration in the main function of the 'main' module"
+ "summary": "Added the 's4' type declaration in the main function"
}
]
},
@@ -134,7 +149,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b52397c136bdd9b41868a929f0d416ee1c6abf97..3ec9ffbcf213c0e967d076756419ac146619b5cd"
+ "shas": "3660aaf9358df40375f73cb4bfb377a1382b7d3e..396230fe3c660ac63e571cbce1e3432349fb42c7"
}
,{
"testCaseDescription": "go-struct-types-replacement-test",
@@ -280,7 +295,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "3ec9ffbcf213c0e967d076756419ac146619b5cd..895c808dc6465df7bf6059e4e773bb901b678834"
+ "shas": "396230fe3c660ac63e571cbce1e3432349fb42c7..44f4a72ca5904799754ac659baa3fd1191c5ae35"
}
,{
"testCaseDescription": "go-struct-types-delete-replacement-test",
@@ -426,7 +441,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "895c808dc6465df7bf6059e4e773bb901b678834..8794ab0649ceafe5f2b499a7313b43a94ece3a30"
+ "shas": "44f4a72ca5904799754ac659baa3fd1191c5ae35..3e3f6aef1912a00d1f54c15a2c9603db93e32783"
}
,{
"testCaseDescription": "go-struct-types-delete-insert-test",
@@ -446,7 +461,7 @@
]
}
},
- "summary": "Deleted the 's1' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 's1' type declaration in the main function"
},
{
"span": {
@@ -461,7 +476,7 @@
]
}
},
- "summary": "Deleted the 's2' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 's2' type declaration in the main function"
},
{
"span": {
@@ -476,7 +491,7 @@
]
}
},
- "summary": "Deleted the 's3' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 's3' type declaration in the main function"
},
{
"span": {
@@ -491,7 +506,7 @@
]
}
},
- "summary": "Deleted the 's4' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 's4' type declaration in the main function"
}
]
},
@@ -522,7 +537,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8794ab0649ceafe5f2b499a7313b43a94ece3a30..604abe90628f68bfb8810ae9d7e6ea0d76547972"
+ "shas": "3e3f6aef1912a00d1f54c15a2c9603db93e32783..a77aaacc58bfdd55c6797f8f3d1fff0b15a8f1d5"
}
,{
"testCaseDescription": "go-struct-types-teardown-test",
@@ -537,12 +552,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -564,5 +594,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "604abe90628f68bfb8810ae9d7e6ea0d76547972..80f368e3e339a6f6cd13071fff11a504b589ebaa"
+ "shas": "a77aaacc58bfdd55c6797f8f3d1fff0b15a8f1d5..d27aeb5e58d624d463c84b7a506673945bee82fd"
}]
diff --git a/test/corpus/diff-summaries/go/switch-statements.json b/test/corpus/diff-summaries/go/switch-statements.json
index b12dcdc1e..6ea195a8b 100644
--- a/test/corpus/diff-summaries/go/switch-statements.json
+++ b/test/corpus/diff-summaries/go/switch-statements.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6e1ebffb2ad214b1c4a7ab7a8efed9b6a25e8470..c86fa331f18f6196397e3ac03e3751626b49f22a"
+ "shas": "08c2e3dcd4ce51ddc9fd673ef182af5f0748761d..57eb15a262867634bb0669a59e07b4703d24240b"
}
,{
"testCaseDescription": "go-switch-statements-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added a switch statement in the main function of the 'main' module"
+ "summary": "Added a switch statement in the main function"
}
]
},
@@ -84,7 +99,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c86fa331f18f6196397e3ac03e3751626b49f22a..fafd2357a4acfa84a9f5b4e59953c2e5ee9bd666"
+ "shas": "57eb15a262867634bb0669a59e07b4703d24240b..727028399225f191e4201a1172376ad9bf6cd0a2"
}
,{
"testCaseDescription": "go-switch-statements-replacement-test",
@@ -279,7 +294,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "fafd2357a4acfa84a9f5b4e59953c2e5ee9bd666..59e626e9c3a21904b5361949d71bcaa64083a9e8"
+ "shas": "727028399225f191e4201a1172376ad9bf6cd0a2..880af6e91564040c1fc0334c6dd9f8a62a6d8cea"
}
,{
"testCaseDescription": "go-switch-statements-delete-replacement-test",
@@ -474,7 +489,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "59e626e9c3a21904b5361949d71bcaa64083a9e8..977098a7b050b573c879012ec716ae25e7009039"
+ "shas": "880af6e91564040c1fc0334c6dd9f8a62a6d8cea..687a060667a15c960b679bd47bad476720b066d2"
}
,{
"testCaseDescription": "go-switch-statements-delete-insert-test",
@@ -494,7 +509,7 @@
]
}
},
- "summary": "Deleted a switch statement in the main function of the 'main' module"
+ "summary": "Deleted a switch statement in the main function"
}
]
},
@@ -520,7 +535,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "977098a7b050b573c879012ec716ae25e7009039..810ba951cb71bf751f77c956ce2666316d21149f"
+ "shas": "687a060667a15c960b679bd47bad476720b066d2..6e7cf473bef3db760568c7999a2e8c832b5e9ab2"
}
,{
"testCaseDescription": "go-switch-statements-teardown-test",
@@ -535,12 +550,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -562,5 +592,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "810ba951cb71bf751f77c956ce2666316d21149f..4c5c96874eeb7170044dd451dcc92cb8f852ec31"
+ "shas": "6e7cf473bef3db760568c7999a2e8c832b5e9ab2..259a41893cf92e7d6ded7e6b963dfc276e4dd3a2"
}]
diff --git a/test/corpus/diff-summaries/go/type-assertion-expressions.json b/test/corpus/diff-summaries/go/type-assertion-expressions.json
index ea773ab43..aee7ca4b7 100644
--- a/test/corpus/diff-summaries/go/type-assertion-expressions.json
+++ b/test/corpus/diff-summaries/go/type-assertion-expressions.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "668c02674516194c0623120c957d1be93af6cde5..a41667e052309ce89c4f555ccef62ea1f8765762"
+ "shas": "39c039e08c3764d56d26a74bbc7bb32704cc398c..bf275213eb7f0252ea00d4c4d512d7c1ad3a841c"
}
,{
"testCaseDescription": "go-type-assertion-expressions-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'x.(z.Person)' type assertion statement in the main function of the 'main' module"
+ "summary": "Added the 'x.(z.Person)' type assertion statement in the main function"
}
]
},
@@ -81,7 +96,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a41667e052309ce89c4f555ccef62ea1f8765762..41c4503413f54d4de3eecfe0dda21cec03dd0bf4"
+ "shas": "bf275213eb7f0252ea00d4c4d512d7c1ad3a841c..90dd626922974beae3ac02734b6a9040c20f8844"
}
,{
"testCaseDescription": "go-type-assertion-expressions-replacement-test",
@@ -113,7 +128,7 @@
}
]
},
- "summary": "Replaced the 'x' identifier with the 'b' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'x' identifier with the 'b' identifier in the main function"
},
{
"span": {
@@ -140,7 +155,7 @@
}
]
},
- "summary": "Replaced the 'z.Person' qualified identifier with the 'c.Dog' qualified identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'z.Person' qualified identifier with the 'c.Dog' qualified identifier in the main function"
}
]
},
@@ -163,7 +178,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "41c4503413f54d4de3eecfe0dda21cec03dd0bf4..7da6d7ad5b540a8e4d65b29ee231d9243b59245e"
+ "shas": "90dd626922974beae3ac02734b6a9040c20f8844..8c6d06fdf10722bafb109c5c8b03922b16b2e4b2"
}
,{
"testCaseDescription": "go-type-assertion-expressions-delete-replacement-test",
@@ -195,7 +210,7 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'x' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'b' identifier with the 'x' identifier in the main function"
},
{
"span": {
@@ -222,7 +237,7 @@
}
]
},
- "summary": "Replaced the 'c.Dog' qualified identifier with the 'z.Person' qualified identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'c.Dog' qualified identifier with the 'z.Person' qualified identifier in the main function"
}
]
},
@@ -245,7 +260,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7da6d7ad5b540a8e4d65b29ee231d9243b59245e..961545675dd701b933d6dd097dbec5c972f857a5"
+ "shas": "8c6d06fdf10722bafb109c5c8b03922b16b2e4b2..428e63d779c812b38a047f0ce6a7c94681735c64"
}
,{
"testCaseDescription": "go-type-assertion-expressions-delete-insert-test",
@@ -265,7 +280,7 @@
]
}
},
- "summary": "Deleted the 'x.(z.Person)' type assertion statement in the main function of the 'main' module"
+ "summary": "Deleted the 'x.(z.Person)' type assertion statement in the main function"
}
]
},
@@ -288,7 +303,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "961545675dd701b933d6dd097dbec5c972f857a5..bc66239ed573f0367fd6330bd280f89c82fa4f0a"
+ "shas": "428e63d779c812b38a047f0ce6a7c94681735c64..3c31becef538d5dc5a68400e14ceff9b10ccca37"
}
,{
"testCaseDescription": "go-type-assertion-expressions-teardown-test",
@@ -303,12 +318,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -330,5 +360,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "bc66239ed573f0367fd6330bd280f89c82fa4f0a..8cdc2760c296eb120ea2b2e67102c869542473e8"
+ "shas": "3c31becef538d5dc5a68400e14ceff9b10ccca37..7b340405bd9a9ab47d50717b924a791be7df4e4c"
}]
diff --git a/test/corpus/diff-summaries/go/type-conversion-expressions.json b/test/corpus/diff-summaries/go/type-conversion-expressions.json
index f91cc9903..1c1caf5c4 100644
--- a/test/corpus/diff-summaries/go/type-conversion-expressions.json
+++ b/test/corpus/diff-summaries/go/type-conversion-expressions.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8cdc2760c296eb120ea2b2e67102c869542473e8..060d556effe82691e9785813855a9ecac4c3d447"
+ "shas": "7b340405bd9a9ab47d50717b924a791be7df4e4c..e06123f66775f44daf42dbea18390891dd4df1d2"
}
,{
"testCaseDescription": "go-type-conversion-expressions-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the '[]a.b(c.d)' type conversion expression in the main function of the 'main' module"
+ "summary": "Added the '[]a.b(c.d)' type conversion expression in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the '([]a.b)(c.d)' type conversion expression in the main function of the 'main' module"
+ "summary": "Added the '([]a.b)(c.d)' type conversion expression in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 'e[f](g)' function call in the main function of the 'main' module"
+ "summary": "Added the 'e[f](g)' function call in the main function"
},
{
"span": {
@@ -103,7 +118,7 @@
]
}
},
- "summary": "Added the 'e[f](g)' function call in the main function of the 'main' module"
+ "summary": "Added the 'e[f](g)' function call in the main function"
}
]
},
@@ -129,7 +144,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "060d556effe82691e9785813855a9ecac4c3d447..dba7ae9fc8a9a4600aa19a679d5bc6590832a890"
+ "shas": "e06123f66775f44daf42dbea18390891dd4df1d2..1079e1f0a50bda389b619cbc8c9ca9197315a2b9"
}
,{
"testCaseDescription": "go-type-conversion-expressions-replacement-test",
@@ -161,7 +176,7 @@
}
]
},
- "summary": "Replaced the 'a.b' qualified identifier with the 'x.y' qualified identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'a.b' qualified identifier with the 'x.y' qualified identifier in the main function"
},
{
"span": {
@@ -242,7 +257,7 @@
}
]
},
- "summary": "Replaced the 'a.b' qualified identifier with the 'f.g' qualified identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'a.b' qualified identifier with the 'f.g' qualified identifier in the main function"
},
{
"span": {
@@ -487,7 +502,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "dba7ae9fc8a9a4600aa19a679d5bc6590832a890..a5265cf460047217db17509db12cb7f501c39614"
+ "shas": "1079e1f0a50bda389b619cbc8c9ca9197315a2b9..f43697697c714dec9e9f0a7ca910b0fe61b3a6a1"
}
,{
"testCaseDescription": "go-type-conversion-expressions-delete-replacement-test",
@@ -519,7 +534,7 @@
}
]
},
- "summary": "Replaced the 'x.y' qualified identifier with the 'a.b' qualified identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'x.y' qualified identifier with the 'a.b' qualified identifier in the main function"
},
{
"span": {
@@ -600,7 +615,7 @@
}
]
},
- "summary": "Replaced the 'f.g' qualified identifier with the 'a.b' qualified identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'f.g' qualified identifier with the 'a.b' qualified identifier in the main function"
},
{
"span": {
@@ -845,7 +860,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a5265cf460047217db17509db12cb7f501c39614..9bafa4b73c30416434a72d73bcf0c361015e479e"
+ "shas": "f43697697c714dec9e9f0a7ca910b0fe61b3a6a1..d23c4aa30ec95311b310f9091a49d55bb5a36ee6"
}
,{
"testCaseDescription": "go-type-conversion-expressions-delete-insert-test",
@@ -865,7 +880,7 @@
]
}
},
- "summary": "Deleted the '[]a.b(c.d)' type conversion expression in the main function of the 'main' module"
+ "summary": "Deleted the '[]a.b(c.d)' type conversion expression in the main function"
},
{
"span": {
@@ -880,7 +895,7 @@
]
}
},
- "summary": "Deleted the '([]a.b)(c.d)' type conversion expression in the main function of the 'main' module"
+ "summary": "Deleted the '([]a.b)(c.d)' type conversion expression in the main function"
},
{
"span": {
@@ -895,7 +910,7 @@
]
}
},
- "summary": "Deleted the 'e[f](g)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'e[f](g)' function call in the main function"
},
{
"span": {
@@ -910,7 +925,7 @@
]
}
},
- "summary": "Deleted the 'e[f](g)' function call in the main function of the 'main' module"
+ "summary": "Deleted the 'e[f](g)' function call in the main function"
}
]
},
@@ -936,7 +951,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9bafa4b73c30416434a72d73bcf0c361015e479e..cc6f207a8227743f511bd5cfa2c09ea9890641e3"
+ "shas": "d23c4aa30ec95311b310f9091a49d55bb5a36ee6..b26659150b0b7be7f597f4b0458b11040dfe685a"
}
,{
"testCaseDescription": "go-type-conversion-expressions-teardown-test",
@@ -951,12 +966,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -978,5 +1008,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "cc6f207a8227743f511bd5cfa2c09ea9890641e3..bee7c2fa1efb34386277ca0b38c74178200faf54"
+ "shas": "b26659150b0b7be7f597f4b0458b11040dfe685a..62e181eaec5ef85a5d7816331750f05ed4be5ed3"
}]
diff --git a/test/corpus/diff-summaries/go/type-declarations.json b/test/corpus/diff-summaries/go/type-declarations.json
index f03b9c367..b320ec83b 100644
--- a/test/corpus/diff-summaries/go/type-declarations.json
+++ b/test/corpus/diff-summaries/go/type-declarations.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "7193c3cab8046a6b2b57792ecbef7f2ad5f318b7..997e04ad887b3f63f5916a484d39b82b21e0a21e"
+ "shas": "407e4c1852d95bd8c9a3494899d65731e2bbb43f..25728b3aea7540b288bdba7aa562fb20ba2019ba"
}
,{
"testCaseDescription": "go-type-declarations-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'a' type declaration in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'a' type declaration in the main function"
},
{
"span": {
@@ -88,7 +103,7 @@
]
}
},
- "summary": "Added the 'c' type declaration in the main function of the 'main' module"
+ "summary": "Added the 'c' type declaration in the main function"
}
]
},
@@ -115,7 +130,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "997e04ad887b3f63f5916a484d39b82b21e0a21e..226a0ad42c1df879c6765ffd98a880b49f4286f1"
+ "shas": "25728b3aea7540b288bdba7aa562fb20ba2019ba..c398853e91bfceb57339f50c32e2076c8edc3f10"
}
,{
"testCaseDescription": "go-type-declarations-replacement-test",
@@ -311,7 +326,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "226a0ad42c1df879c6765ffd98a880b49f4286f1..b5068ea221a9731fae1c7d524ca4dd9821bc7b3d"
+ "shas": "c398853e91bfceb57339f50c32e2076c8edc3f10..15b226c3776ba2ca08c06e3d61ee6ccfc4ccd4ef"
}
,{
"testCaseDescription": "go-type-declarations-delete-replacement-test",
@@ -507,7 +522,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b5068ea221a9731fae1c7d524ca4dd9821bc7b3d..5e5e473cd63105a7795c6570d5d73e7bbd1280ea"
+ "shas": "15b226c3776ba2ca08c06e3d61ee6ccfc4ccd4ef..7bebec4a6a031168e3daaaf0be17c5bdb981c2ff"
}
,{
"testCaseDescription": "go-type-declarations-delete-insert-test",
@@ -527,7 +542,7 @@
]
}
},
- "summary": "Deleted the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'a' type declaration in the main function"
},
{
"span": {
@@ -542,7 +557,7 @@
]
}
},
- "summary": "Deleted the 'a' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'a' type declaration in the main function"
},
{
"span": {
@@ -557,7 +572,7 @@
]
}
},
- "summary": "Deleted the 'c' type declaration in the main function of the 'main' module"
+ "summary": "Deleted the 'c' type declaration in the main function"
}
]
},
@@ -584,7 +599,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "5e5e473cd63105a7795c6570d5d73e7bbd1280ea..0ea75c3e64c69c71df42e9afad3038188c8fa020"
+ "shas": "7bebec4a6a031168e3daaaf0be17c5bdb981c2ff..882eb3c2516e2c1dd64e1ced273a98c461e247c9"
}
,{
"testCaseDescription": "go-type-declarations-teardown-test",
@@ -599,12 +614,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -626,5 +656,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "0ea75c3e64c69c71df42e9afad3038188c8fa020..cbaa77e08635ce41d412574590df4152cae3e4bc"
+ "shas": "882eb3c2516e2c1dd64e1ced273a98c461e247c9..8b23ffed2230fe0c2e75c1a02c179c9ff1726d8f"
}]
diff --git a/test/corpus/diff-summaries/go/type-switch-statements.json b/test/corpus/diff-summaries/go/type-switch-statements.json
index 3883fce83..1d9cb3db7 100644
--- a/test/corpus/diff-summaries/go/type-switch-statements.json
+++ b/test/corpus/diff-summaries/go/type-switch-statements.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "4c5c96874eeb7170044dd451dcc92cb8f852ec31..da66ddde911a1d26b2d8d388027db09d8cfaccaf"
+ "shas": "259a41893cf92e7d6ded7e6b963dfc276e4dd3a2..8dce6e38a34b47bc8ab779bdea2e6a3f2eb32eeb"
}
,{
"testCaseDescription": "go-type-switch-statements-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'e' switch statement in the main function of the 'main' module"
+ "summary": "Added the 'e' switch statement in the main function"
}
]
},
@@ -86,7 +101,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "da66ddde911a1d26b2d8d388027db09d8cfaccaf..c2416cc9d2b6aa03bb39c797332c3a2dbbb3aadf"
+ "shas": "8dce6e38a34b47bc8ab779bdea2e6a3f2eb32eeb..fe7af65017235cb0aa5b1cf9596dc880467a830b"
}
,{
"testCaseDescription": "go-type-switch-statements-replacement-test",
@@ -143,7 +158,7 @@
" case *Dog:"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c2416cc9d2b6aa03bb39c797332c3a2dbbb3aadf..8f2aea4bcb8da8f7c64a86bc338497b0e7fc69c5"
+ "shas": "fe7af65017235cb0aa5b1cf9596dc880467a830b..5550ebeea097dfc8b61407ac282806a1eb239051"
}
,{
"testCaseDescription": "go-type-switch-statements-delete-replacement-test",
@@ -200,7 +215,7 @@
" case *Dog:"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8f2aea4bcb8da8f7c64a86bc338497b0e7fc69c5..a7781525b33688effa3e79836f8902782f74c427"
+ "shas": "5550ebeea097dfc8b61407ac282806a1eb239051..4c882301284f37700ebed2cb52f4bfdc407c1fce"
}
,{
"testCaseDescription": "go-type-switch-statements-delete-insert-test",
@@ -220,7 +235,7 @@
]
}
},
- "summary": "Deleted the 'e' switch statement in the main function of the 'main' module"
+ "summary": "Deleted the 'e' switch statement in the main function"
}
]
},
@@ -248,7 +263,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a7781525b33688effa3e79836f8902782f74c427..5bd6c81f2a297de8cdf8f186d8b834e893c1f78f"
+ "shas": "4c882301284f37700ebed2cb52f4bfdc407c1fce..6a8743c7c0edf3f07d48d3f7c2e2c04583c4bd04"
}
,{
"testCaseDescription": "go-type-switch-statements-teardown-test",
@@ -263,12 +278,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -290,5 +320,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "5bd6c81f2a297de8cdf8f186d8b834e893c1f78f..a5c82828c92a590f5a64d58dd4a626b294a2c565"
+ "shas": "6a8743c7c0edf3f07d48d3f7c2e2c04583c4bd04..cb913819d62f34c2cc72aa293b39fabca1a0f05c"
}]
diff --git a/test/corpus/diff-summaries/go/unary-expressions.json b/test/corpus/diff-summaries/go/unary-expressions.json
index 0fee2b567..f59ab40af 100644
--- a/test/corpus/diff-summaries/go/unary-expressions.json
+++ b/test/corpus/diff-summaries/go/unary-expressions.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "bee7c2fa1efb34386277ca0b38c74178200faf54..ff56fcf05a07472f07956bf2d2b259658ae68b0b"
+ "shas": "62e181eaec5ef85a5d7816331750f05ed4be5ed3..ad7c2d4b1b3af4d629262b596d4d76591b0f2939"
}
,{
"testCaseDescription": "go-unary-expressions-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the '!<-a' operator in the main function of the 'main' module"
+ "summary": "Added the '!<-a' operator in the main function"
},
{
"span": {
@@ -73,7 +88,7 @@
]
}
},
- "summary": "Added the '*foo()' operator in the main function of the 'main' module"
+ "summary": "Added the '*foo()' operator in the main function"
}
]
},
@@ -97,7 +112,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ff56fcf05a07472f07956bf2d2b259658ae68b0b..1a5ce5871077dfe3c63a9af84f81b078f35d8c70"
+ "shas": "ad7c2d4b1b3af4d629262b596d4d76591b0f2939..857884599a5b10f98e339f72e7e0ef5dff6ea432"
}
,{
"testCaseDescription": "go-unary-expressions-replacement-test",
@@ -129,7 +144,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'b' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'a' identifier with the 'b' identifier in the main function"
},
{
"span": {
@@ -181,7 +196,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "1a5ce5871077dfe3c63a9af84f81b078f35d8c70..8650a686e3cce038628c50e77b00a5ff7943bfd8"
+ "shas": "857884599a5b10f98e339f72e7e0ef5dff6ea432..dacb9cd739035ebe3919a96f7f90cd75e48b832e"
}
,{
"testCaseDescription": "go-unary-expressions-delete-replacement-test",
@@ -213,7 +228,7 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'a' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'b' identifier with the 'a' identifier in the main function"
},
{
"span": {
@@ -265,7 +280,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8650a686e3cce038628c50e77b00a5ff7943bfd8..91bf29df3a0efe16134c69b6a8af7c63a7a62541"
+ "shas": "dacb9cd739035ebe3919a96f7f90cd75e48b832e..5ef7adc637975b15415197ba4e8ce354e69789fd"
}
,{
"testCaseDescription": "go-unary-expressions-delete-insert-test",
@@ -285,7 +300,7 @@
]
}
},
- "summary": "Deleted the '!<-a' operator in the main function of the 'main' module"
+ "summary": "Deleted the '!<-a' operator in the main function"
},
{
"span": {
@@ -300,7 +315,7 @@
]
}
},
- "summary": "Deleted the '*foo()' operator in the main function of the 'main' module"
+ "summary": "Deleted the '*foo()' operator in the main function"
}
]
},
@@ -324,7 +339,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "91bf29df3a0efe16134c69b6a8af7c63a7a62541..b338ed0baff81143d1d5d24cd717b936335955b7"
+ "shas": "5ef7adc637975b15415197ba4e8ce354e69789fd..30d627648cb775a76037cf8a7ab0f03c8588727b"
}
,{
"testCaseDescription": "go-unary-expressions-teardown-test",
@@ -339,12 +354,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -366,5 +396,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b338ed0baff81143d1d5d24cd717b936335955b7..bd47547e797a6e76a34e259077fc32181d6667f5"
+ "shas": "30d627648cb775a76037cf8a7ab0f03c8588727b..6ea06aa1e8431651d63087d1f623f409947a25f1"
}]
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 95d56a29b..402dbbd0c 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
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "beaafb3d07a00910a1446a55ba991cc61f22aa65..f23f1b776ac8b43fcb4ffbd5ff576564a0e407f8"
+ "shas": "ba8c45bc969c0974d427789ea9cf408475593b4f..7d82093dc2c65d42e401f7a495fbe70a7cd7ed19"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-insert-test",
@@ -54,11 +69,11 @@
],
"end": [
4,
- 9
+ 13
]
}
},
- "summary": "Added the 'zero' variable in the main function of the 'main' module"
+ "summary": "Added the 'zero' var assignment in the main function"
},
{
"span": {
@@ -69,26 +84,11 @@
],
"end": [
5,
- 8
+ 20
]
}
},
- "summary": "Added the 'one' variable in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 10
- ],
- "end": [
- 5,
- 13
- ]
- }
- },
- "summary": "Added the 'two' variable in the main function of the 'main' module"
+ "summary": "Added the 'one, two' var assignment in the main function"
}
]
},
@@ -112,7 +112,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "f23f1b776ac8b43fcb4ffbd5ff576564a0e407f8..ab684a45678699db4bf01cc3613b936f7b785c22"
+ "shas": "7d82093dc2c65d42e401f7a495fbe70a7cd7ed19..419274e5020690ffdfc80fa234fcead2517443e0"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-replacement-test",
@@ -144,7 +144,7 @@
}
]
},
- "summary": "Replaced the 'zero' identifier with the 'a' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'zero' identifier with the 'a' identifier in the a var assignment of the 'main' function"
},
{
"span": {
@@ -171,7 +171,7 @@
}
]
},
- "summary": "Replaced the 'one' identifier with the 'b' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'one' identifier with the 'b' identifier in the b, c var assignment of the 'main' function"
},
{
"span": {
@@ -198,7 +198,7 @@
}
]
},
- "summary": "Replaced the 'two' identifier with the 'c' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'two' identifier with the 'c' identifier in the b, c var assignment of the 'main' function"
}
]
},
@@ -223,7 +223,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ab684a45678699db4bf01cc3613b936f7b785c22..a6ef8521dd858d3ada22ca793179985b651835c1"
+ "shas": "419274e5020690ffdfc80fa234fcead2517443e0..882172cbcf5efc650425926516515d7ad0104fad"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-delete-replacement-test",
@@ -255,7 +255,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'zero' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'a' identifier with the 'zero' identifier in the zero var assignment of the 'main' function"
},
{
"span": {
@@ -282,7 +282,7 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'one' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'b' identifier with the 'one' identifier in the one, two var assignment of the 'main' function"
},
{
"span": {
@@ -309,7 +309,7 @@
}
]
},
- "summary": "Replaced the 'c' identifier with the 'two' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'c' identifier with the 'two' identifier in the one, two var assignment of the 'main' function"
}
]
},
@@ -334,7 +334,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a6ef8521dd858d3ada22ca793179985b651835c1..8ad019fda61a53d0fbc5438d5cd29ad3c8182152"
+ "shas": "882172cbcf5efc650425926516515d7ad0104fad..d9003bce5e60e442e3c65bd64ce31f514f56d5be"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-delete-insert-test",
@@ -350,11 +350,11 @@
],
"end": [
4,
- 9
+ 13
]
}
},
- "summary": "Deleted the 'zero' variable in the main function of the 'main' module"
+ "summary": "Deleted the 'zero' var assignment in the main function"
},
{
"span": {
@@ -365,26 +365,11 @@
],
"end": [
5,
- 8
+ 20
]
}
},
- "summary": "Deleted the 'one' variable in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 10
- ],
- "end": [
- 5,
- 13
- ]
- }
- },
- "summary": "Deleted the 'two' variable in the main function of the 'main' module"
+ "summary": "Deleted the 'one, two' var assignment in the main function"
}
]
},
@@ -408,7 +393,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8ad019fda61a53d0fbc5438d5cd29ad3c8182152..d7aa7780028d8b79dcd30f425239703123a19c15"
+ "shas": "d9003bce5e60e442e3c65bd64ce31f514f56d5be..83bedace90d82120d06cc87c9e2993bafcd75174"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-teardown-test",
@@ -423,12 +408,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -450,5 +450,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d7aa7780028d8b79dcd30f425239703123a19c15..e75c5ac355ded95806073c70e83be9e9b3634163"
+ "shas": "83bedace90d82120d06cc87c9e2993bafcd75174..3dba2a559a0cc46933a2663e7b9cdcd4a92808d9"
}]
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 994dcc2c0..ffb8b0b13 100644
--- a/test/corpus/diff-summaries/go/var-declarations-with-types.json
+++ b/test/corpus/diff-summaries/go/var-declarations-with-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "166ab1d1dfa2b18943f9d328cc47a34b4e4288fa..c72c09d81f43fbcbe4836588ced1f3a4fb63731f"
+ "shas": "e314d296ac8ddd2fee51a4cf45b812637d285244..3a54778e8643fed461c68e500e8eb6aa0ee72ab1"
}
,{
"testCaseDescription": "go-var-declarations-with-types-insert-test",
@@ -52,13 +67,43 @@
4,
5
],
+ "end": [
+ 4,
+ 9
+ ]
+ }
+ },
+ "summary": "Added the 'zero' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 10
+ ],
+ "end": [
+ 4,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the 'int' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 16
+ ],
"end": [
4,
17
]
}
},
- "summary": "Added the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Added '0' in the main function"
},
{
"span": {
@@ -69,18 +114,63 @@
],
"end": [
5,
- 27
+ 8
]
}
},
- "summary": "Added the 'one' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'one' identifier in the main function"
},
{
"span": {
"insert": {
"start": [
5,
- 5
+ 10
+ ],
+ "end": [
+ 5,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the 'two' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 14
+ ],
+ "end": [
+ 5,
+ 20
+ ]
+ }
+ },
+ "summary": "Added the 'uint64' identifier in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 23
+ ],
+ "end": [
+ 5,
+ 24
+ ]
+ }
+ },
+ "summary": "Added '1' in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 26
],
"end": [
5,
@@ -88,7 +178,7 @@
]
}
},
- "summary": "Added the 'two' var assignment in the main function of the 'main' module"
+ "summary": "Added '2' in the main function"
}
]
},
@@ -112,7 +202,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "c72c09d81f43fbcbe4836588ced1f3a4fb63731f..46f18357b783f8a73ac8112e238e667ff4bc1378"
+ "shas": "3a54778e8643fed461c68e500e8eb6aa0ee72ab1..23e6404f39f85f4a31a72cb893ea7145518ca0c6"
}
,{
"testCaseDescription": "go-var-declarations-with-types-replacement-test",
@@ -144,7 +234,7 @@
}
]
},
- "summary": "Replaced the 'zero' identifier with the 'a' identifier in the a var assignment of the 'main' function"
+ "summary": "Replaced the 'zero' identifier with the 'a' identifier in the main function"
},
{
"span": {
@@ -171,7 +261,7 @@
}
]
},
- "summary": "Replaced the 'one' identifier with the 'b' identifier in the b var assignment of the 'main' function"
+ "summary": "Replaced the 'one' identifier with the 'b' identifier in the main function"
},
{
"span": {
@@ -198,7 +288,7 @@
}
]
},
- "summary": "Replaced the 'two' identifier with the 'c' identifier in the c var assignment of the 'main' function"
+ "summary": "Replaced the 'two' identifier with the 'c' identifier in the main function"
}
]
},
@@ -223,7 +313,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "46f18357b783f8a73ac8112e238e667ff4bc1378..e7e4dfb126d1a6b2fb2bf72dd548beda84ffbfb4"
+ "shas": "23e6404f39f85f4a31a72cb893ea7145518ca0c6..c239ed4dccd2c65ccb5a7293327ebba940ad92b6"
}
,{
"testCaseDescription": "go-var-declarations-with-types-delete-replacement-test",
@@ -255,7 +345,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'zero' identifier in the zero var assignment of the 'main' function"
+ "summary": "Replaced the 'a' identifier with the 'zero' identifier in the main function"
},
{
"span": {
@@ -282,7 +372,7 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'one' identifier in the one var assignment of the 'main' function"
+ "summary": "Replaced the 'b' identifier with the 'one' identifier in the main function"
},
{
"span": {
@@ -309,7 +399,7 @@
}
]
},
- "summary": "Replaced the 'c' identifier with the 'two' identifier in the two var assignment of the 'main' function"
+ "summary": "Replaced the 'c' identifier with the 'two' identifier in the main function"
}
]
},
@@ -334,7 +424,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "e7e4dfb126d1a6b2fb2bf72dd548beda84ffbfb4..82cfefb733a9091542c79228bb43a5cbcc284228"
+ "shas": "c239ed4dccd2c65ccb5a7293327ebba940ad92b6..f1c07b4aa5c85609e85929fcd6a42fe1270cb9d8"
}
,{
"testCaseDescription": "go-var-declarations-with-types-delete-insert-test",
@@ -348,13 +438,43 @@
4,
5
],
+ "end": [
+ 4,
+ 9
+ ]
+ }
+ },
+ "summary": "Deleted the 'zero' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 10
+ ],
+ "end": [
+ 4,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'int' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 16
+ ],
"end": [
4,
17
]
}
},
- "summary": "Deleted the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Deleted '0' in the main function"
},
{
"span": {
@@ -365,18 +485,63 @@
],
"end": [
5,
- 27
+ 8
]
}
},
- "summary": "Deleted the 'one' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'one' identifier in the main function"
},
{
"span": {
"delete": {
"start": [
5,
- 5
+ 10
+ ],
+ "end": [
+ 5,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'two' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 14
+ ],
+ "end": [
+ 5,
+ 20
+ ]
+ }
+ },
+ "summary": "Deleted the 'uint64' identifier in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 23
+ ],
+ "end": [
+ 5,
+ 24
+ ]
+ }
+ },
+ "summary": "Deleted '1' in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 26
],
"end": [
5,
@@ -384,7 +549,7 @@
]
}
},
- "summary": "Deleted the 'two' var assignment in the main function of the 'main' module"
+ "summary": "Deleted '2' in the main function"
}
]
},
@@ -408,7 +573,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "82cfefb733a9091542c79228bb43a5cbcc284228..9d2bb849a481840629ed6bcb2a17afc5e8e49a50"
+ "shas": "f1c07b4aa5c85609e85929fcd6a42fe1270cb9d8..8712527e7cc3056ebb8d176db32429befc4976a8"
}
,{
"testCaseDescription": "go-var-declarations-with-types-teardown-test",
@@ -423,12 +588,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -450,5 +630,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "9d2bb849a481840629ed6bcb2a17afc5e8e49a50..beaafb3d07a00910a1446a55ba991cc61f22aa65"
+ "shas": "8712527e7cc3056ebb8d176db32429befc4976a8..ba8c45bc969c0974d427789ea9cf408475593b4f"
}]
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 ac02c255a..708e896f5 100644
--- a/test/corpus/diff-summaries/go/var-declarations-without-types.json
+++ b/test/corpus/diff-summaries/go/var-declarations-without-types.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "d7c7c21bb12a3b1d9bc3d7ac212a3bdada677d71..a5335e2199db7d1bb83520b275684bccb917d0ec"
+ "shas": "9c509bdfabb537255c810cd09cf45b53bf65628f..6241b8182026cf5a9a5ebb20894a2066ad61d7fa"
}
,{
"testCaseDescription": "go-var-declarations-without-types-insert-test",
@@ -58,7 +73,7 @@
]
}
},
- "summary": "Added the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Added the 'zero' var assignment in the main function"
}
]
},
@@ -81,7 +96,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "a5335e2199db7d1bb83520b275684bccb917d0ec..433d75dc1cf7583ffafeaddfe1742fe6c5024680"
+ "shas": "6241b8182026cf5a9a5ebb20894a2066ad61d7fa..4381dbdfbfc360ed15534ae1563ca7f307ba6fa3"
}
,{
"testCaseDescription": "go-var-declarations-without-types-replacement-test",
@@ -113,7 +128,22 @@
}
]
},
- "summary": "Replaced the 'zero' identifier with the 'one' identifier in the one var assignment of the 'main' function"
+ "summary": "Replaced the 'zero' identifier with the 'one' identifier in the one, two var assignment of the 'main' function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 10
+ ],
+ "end": [
+ 4,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the 'two' identifier in the one, two var assignment of the 'main' function"
},
{
"span": {
@@ -140,14 +170,14 @@
}
]
},
- "summary": "Replaced '0' with '1' in the one var assignment of the 'main' function"
+ "summary": "Replaced '0' with '1' in the one, two var assignment of the 'main' function"
},
{
"span": {
"insert": {
"start": [
4,
- 5
+ 19
],
"end": [
4,
@@ -155,7 +185,7 @@
]
}
},
- "summary": "Added the 'two' var assignment in the main function of the 'main' module"
+ "summary": "Added '2' in the one, two var assignment of the 'main' function"
}
]
},
@@ -178,7 +208,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "433d75dc1cf7583ffafeaddfe1742fe6c5024680..ff82d77c3bc0e5e12d28e5f0f9c19ff110e613f9"
+ "shas": "4381dbdfbfc360ed15534ae1563ca7f307ba6fa3..9e0bc36d4a23fcf88bbe39573c3060fb6c63a244"
}
,{
"testCaseDescription": "go-var-declarations-without-types-delete-replacement-test",
@@ -212,6 +242,21 @@
},
"summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero var assignment of the 'main' function"
},
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 10
+ ],
+ "end": [
+ 4,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'two' identifier in the zero var assignment of the 'main' function"
+ },
{
"span": {
"replace": [
@@ -244,7 +289,7 @@
"delete": {
"start": [
4,
- 5
+ 19
],
"end": [
4,
@@ -252,7 +297,7 @@
]
}
},
- "summary": "Deleted the 'two' var assignment in the main function of the 'main' module"
+ "summary": "Deleted '2' in the zero var assignment of the 'main' function"
}
]
},
@@ -275,7 +320,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "ff82d77c3bc0e5e12d28e5f0f9c19ff110e613f9..8eea9984326d8bd0bda50b717d44cab9f6ff80cc"
+ "shas": "9e0bc36d4a23fcf88bbe39573c3060fb6c63a244..4d38dbeeb84c79bab4cd292803c2a9d6a8d2174a"
}
,{
"testCaseDescription": "go-var-declarations-without-types-delete-insert-test",
@@ -295,7 +340,7 @@
]
}
},
- "summary": "Deleted the 'zero' var assignment in the main function of the 'main' module"
+ "summary": "Deleted the 'zero' var assignment in the main function"
}
]
},
@@ -318,7 +363,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "8eea9984326d8bd0bda50b717d44cab9f6ff80cc..87768b01d903d82a18843fe351755f1eaae28448"
+ "shas": "4d38dbeeb84c79bab4cd292803c2a9d6a8d2174a..b53811b73269e4466e33c70b3ce6619faee5a414"
}
,{
"testCaseDescription": "go-var-declarations-without-types-teardown-test",
@@ -333,12 +378,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -360,5 +420,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "87768b01d903d82a18843fe351755f1eaae28448..166ab1d1dfa2b18943f9d328cc47a34b4e4288fa"
+ "shas": "b53811b73269e4466e33c70b3ce6619faee5a414..e314d296ac8ddd2fee51a4cf45b812637d285244"
}]
diff --git a/test/corpus/diff-summaries/go/variadic-function-declarations.json b/test/corpus/diff-summaries/go/variadic-function-declarations.json
index 31153ff8f..ba19781d2 100644
--- a/test/corpus/diff-summaries/go/variadic-function-declarations.json
+++ b/test/corpus/diff-summaries/go/variadic-function-declarations.json
@@ -11,12 +11,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Added the 'main' module"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'main' function"
}
]
},
@@ -38,7 +53,7 @@
"+}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "6eefcab8de06ce411a43f0fe718199942aa7d74b..cbc15452a6708013f0559031ebb0190234de7422"
+ "shas": "aa75d831de9909c8ed71c01ca49d0b4ef4e4b7e8..9db615e38de5c59ee4b97268aabc270c799757eb"
}
,{
"testCaseDescription": "go-variadic-function-declarations-insert-test",
@@ -58,67 +73,7 @@
]
}
},
- "summary": "Added the '{}' block in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 8
- ]
- }
- },
- "summary": "Added the 'f2' identifier in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 9
- ],
- "end": [
- 5,
- 15
- ]
- }
- },
- "summary": "Added the '...int' parameter declaration in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 5,
- 17
- ],
- "end": [
- 5,
- 19
- ]
- }
- },
- "summary": "Added the '{}' block in the main function of the 'main' module"
- },
- {
- "span": {
- "insert": {
- "start": [
- 6,
- 1
- ],
- "end": [
- 6,
- 23
- ]
- }
- },
- "summary": "Added the 'f3' function in the main function of the 'main' module"
+ "summary": "Added the '{}' expression statements in the main function"
}
]
},
@@ -137,7 +92,22 @@
]
}
},
- "summary": "Added 'func f1(a ...*int)' at line 4, column 1 - line 4, column 19 in the main function of the 'main' module"
+ "summary": "Added 'func f1(a ...*int)' at line 4, column 1 - line 4, column 19 in the main function"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 7,
+ 1
+ ]
+ }
+ },
+ "summary": "Added 'func f2(...int) {}\nfunc f3(a, ...bool) {}\n' at line 5, column 1 - line 7, column 1 in the main function"
}
]
}
@@ -161,7 +131,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "cbc15452a6708013f0559031ebb0190234de7422..b5a661d6c9c6eda94de5c3e4bf688ce16f57692a"
+ "shas": "9db615e38de5c59ee4b97268aabc270c799757eb..e6d1f6dee30000099d39ae30f4e31285dcd8a0a0"
}
,{
"testCaseDescription": "go-variadic-function-declarations-replacement-test",
@@ -193,7 +163,7 @@
}
]
},
- "summary": "Replaced the 'f1' identifier with the 'g1' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'f1' identifier with the 'g1' identifier in the main function"
},
{
"span": {
@@ -220,7 +190,7 @@
}
]
},
- "summary": "Replaced the 'f2' identifier with the 'g2' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'f2' identifier with the 'g2' identifier in the main function"
},
{
"span": {
@@ -274,7 +244,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "b5a661d6c9c6eda94de5c3e4bf688ce16f57692a..49205166c96eb0c07161f0e204911499761b30bc"
+ "shas": "e6d1f6dee30000099d39ae30f4e31285dcd8a0a0..4f6a3884d5c4e05ef0cdb21e07836f3d7d353e2d"
}
,{
"testCaseDescription": "go-variadic-function-declarations-delete-replacement-test",
@@ -306,7 +276,7 @@
}
]
},
- "summary": "Replaced the 'g1' identifier with the 'f1' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'g1' identifier with the 'f1' identifier in the main function"
},
{
"span": {
@@ -333,7 +303,7 @@
}
]
},
- "summary": "Replaced the 'g2' identifier with the 'f2' identifier in the main function of the 'main' module"
+ "summary": "Replaced the 'g2' identifier with the 'f2' identifier in the main function"
},
{
"span": {
@@ -387,7 +357,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "49205166c96eb0c07161f0e204911499761b30bc..400b767878ef457aa783e1fe6d9448a474322df9"
+ "shas": "4f6a3884d5c4e05ef0cdb21e07836f3d7d353e2d..90853de5caa0e260fa11b902eaa7475ebdf99232"
}
,{
"testCaseDescription": "go-variadic-function-declarations-delete-insert-test",
@@ -407,67 +377,7 @@
]
}
},
- "summary": "Deleted the '{}' block in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 6
- ],
- "end": [
- 5,
- 8
- ]
- }
- },
- "summary": "Deleted the 'f2' identifier in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 9
- ],
- "end": [
- 5,
- 15
- ]
- }
- },
- "summary": "Deleted the '...int' parameter declaration in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 5,
- 17
- ],
- "end": [
- 5,
- 19
- ]
- }
- },
- "summary": "Deleted the '{}' block in the main function of the 'main' module"
- },
- {
- "span": {
- "delete": {
- "start": [
- 6,
- 1
- ],
- "end": [
- 6,
- 23
- ]
- }
- },
- "summary": "Deleted the 'f3' function in the main function of the 'main' module"
+ "summary": "Deleted the '{}' expression statements in the main function"
}
]
},
@@ -486,7 +396,22 @@
]
}
},
- "summary": "Deleted 'func f1(a ...*int)' at line 4, column 1 - line 4, column 19 in the main function of the 'main' module"
+ "summary": "Deleted 'func f1(a ...*int)' at line 4, column 1 - line 4, column 19 in the main function"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 7,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted 'func f2(...int) {}\nfunc f3(a, ...bool) {}\n' at line 5, column 1 - line 7, column 1 in the main function"
}
]
}
@@ -510,7 +435,7 @@
" }"
],
"gitDir": "test/corpus/repos/go",
- "shas": "400b767878ef457aa783e1fe6d9448a474322df9..cdcea7ca79996d80a7294a25aaafc60468b769ae"
+ "shas": "90853de5caa0e260fa11b902eaa7475ebdf99232..c5a13455d55bc14c5ff37ddbd752df78ca9cb4b2"
}
,{
"testCaseDescription": "go-variadic-function-declarations-teardown-test",
@@ -525,12 +450,27 @@
1
],
"end": [
- 6,
- 1
+ 1,
+ 13
]
}
},
"summary": "Deleted the 'main' module"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'main' function"
}
]
},
@@ -552,5 +492,5 @@
"-}"
],
"gitDir": "test/corpus/repos/go",
- "shas": "cdcea7ca79996d80a7294a25aaafc60468b769ae..2e4178577ebab07e2229a6846523de7a1a01d863"
+ "shas": "c5a13455d55bc14c5ff37ddbd752df78ca9cb4b2..a8adfaba3e02d1f9416a61ff929abbed0bc123d4"
}]
diff --git a/test/corpus/diff-summaries/javascript/anonymous-function.json b/test/corpus/diff-summaries/javascript/anonymous-function.json
index 2936ff14e..e5b3e427e 100644
--- a/test/corpus/diff-summaries/javascript/anonymous-function.json
+++ b/test/corpus/diff-summaries/javascript/anonymous-function.json
@@ -34,7 +34,7 @@
"+function(a,b) { return a + b; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "07a785cb4f0cfa49a60fdfbbce7d8ecbfd2a820b..1ecbe6a443a701cf2b90740825d337914c3b01b8"
+ "shas": "5bd86096402e987462d865b5963d5e68f31ef22d..ba054a01632544846e183487e942b55c700841d4"
}
,{
"testCaseDescription": "javascript-anonymous-function-replacement-insert-test",
@@ -89,7 +89,7 @@
" function(a,b) { return a + b; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1ecbe6a443a701cf2b90740825d337914c3b01b8..1e649afd16b0e9145c760bd152b90dbf2eeb1c79"
+ "shas": "ba054a01632544846e183487e942b55c700841d4..4e386f088a9b83fb0712ede76f926ec4ab503bcc"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-insert-test",
@@ -196,7 +196,7 @@
" function(a,b) { return a + b; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1e649afd16b0e9145c760bd152b90dbf2eeb1c79..7fb344d8f58ce3935df46d0dc70e9f8f1896908f"
+ "shas": "4e386f088a9b83fb0712ede76f926ec4ab503bcc..37cd59e66cfa065774478f33d8c62adefe5459db"
}
,{
"testCaseDescription": "javascript-anonymous-function-replacement-test",
@@ -303,7 +303,7 @@
" function(a,b) { return a + b; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7fb344d8f58ce3935df46d0dc70e9f8f1896908f..6d835d52398bfc6715ef4c40d2706dd8c11cb83a"
+ "shas": "37cd59e66cfa065774478f33d8c62adefe5459db..14d01e8232e8ab4ef9923517701cea5a39d9a06e"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-replacement-test",
@@ -374,7 +374,7 @@
"+function(b,c) { return b * c; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6d835d52398bfc6715ef4c40d2706dd8c11cb83a..fa0cd2354feb5199209c9aa13525567951185c88"
+ "shas": "14d01e8232e8ab4ef9923517701cea5a39d9a06e..62def272c237a2ea3061d38022bca1545f62425f"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-test",
@@ -413,7 +413,7 @@
" function(b,c) { return b * c; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "fa0cd2354feb5199209c9aa13525567951185c88..a93d062ea69a6600b3f795d769e2557042925d66"
+ "shas": "62def272c237a2ea3061d38022bca1545f62425f..9c2e4c2c0015178634b7747dbc99adffc733ad14"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-rest-test",
@@ -451,5 +451,5 @@
"-function(b,c) { return b * c; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "a93d062ea69a6600b3f795d769e2557042925d66..80946fe6667b3843c0bd704136ac929ca5f2e3e0"
+ "shas": "9c2e4c2c0015178634b7747dbc99adffc733ad14..c18d7bf565cc21b4eab97bee06b8182d71f79310"
}]
diff --git a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json
index f9fe5f636..134088202 100644
--- a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json
+++ b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
- "index e69de29..4a26ae8 100644",
+ "index e69de29b..4a26ae86 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -0,0 +1 @@",
"+function() { return 'hi'; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2a5f85a471c9c83f2e835139afa5eb7bfecd546a..a2527ab39dbaa7651e66e24f3d143d11060841f6"
+ "shas": "c18d7bf565cc21b4eab97bee06b8182d71f79310..8872d92c96b47e465013ae1cd75ddd7bb7ab0f78"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
- "index 4a26ae8..c31dd4b 100644",
+ "index 4a26ae86..c31dd4b7 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" function() { return 'hi'; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "a2527ab39dbaa7651e66e24f3d143d11060841f6..4b3321e8a707ad91af6735319257f7f68fb593b7"
+ "shas": "8872d92c96b47e465013ae1cd75ddd7bb7ab0f78..c76f6c6269c776c99d92fd30687cfa77e62ea746"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
- "index c31dd4b..6b1efa4 100644",
+ "index c31dd4b7..6b1efa42 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" function() { return 'hi'; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4b3321e8a707ad91af6735319257f7f68fb593b7..a01626612654464812b9cedaad745f686edc8138"
+ "shas": "c76f6c6269c776c99d92fd30687cfa77e62ea746..332ec447157ee23778ae3857a5a01f9e10ece1cc"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
- "index 6b1efa4..c31dd4b 100644",
+ "index 6b1efa42..c31dd4b7 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" function() { return 'hi'; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "a01626612654464812b9cedaad745f686edc8138..d640dfcedbbda8708bb8c679b2b96460e63e8e53"
+ "shas": "332ec447157ee23778ae3857a5a01f9e10ece1cc..795ada7689a6f349ad93621970b5f5ec5332ac86"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
- "index c31dd4b..b8e05c0 100644",
+ "index c31dd4b7..b8e05c0e 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+function() { return 'hello'; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d640dfcedbbda8708bb8c679b2b96460e63e8e53..f1436a17d64c050a7d6aa15fe0876ce3fc4176f0"
+ "shas": "795ada7689a6f349ad93621970b5f5ec5332ac86..83f67f1b48452e4d9b163a320152ae9dc8ef403a"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
- "index b8e05c0..ce1ef83 100644",
+ "index b8e05c0e..ce1ef833 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" function() { return 'hello'; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f1436a17d64c050a7d6aa15fe0876ce3fc4176f0..1bd2372f874ec3588d5510b5c7fa50c378b5e665"
+ "shas": "83f67f1b48452e4d9b163a320152ae9dc8ef403a..3a2d2bcd317d7b045070c4d90d694fc69c5b1f38"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
- "index ce1ef83..e69de29 100644",
+ "index ce1ef833..e69de29b 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1 +0,0 @@",
"-function() { return 'hello'; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1bd2372f874ec3588d5510b5c7fa50c378b5e665..e66b1b20abc596d2b560eaa80f1749c79816f9ff"
+ "shas": "3a2d2bcd317d7b045070c4d90d694fc69c5b1f38..aab57fb5b99b7d08c03849736ffa873c26495bec"
}]
diff --git a/test/corpus/diff-summaries/javascript/array.json b/test/corpus/diff-summaries/javascript/array.json
index 335364806..409e5dbdb 100644
--- a/test/corpus/diff-summaries/javascript/array.json
+++ b/test/corpus/diff-summaries/javascript/array.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/array.js b/array.js",
- "index e69de29..3335582 100644",
+ "index e69de29b..33355825 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -0,0 +1 @@",
"+[ \"item1\" ];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "654a538b26c9b4c8637e6c2e4cd497c93e690310..cbf013688399920af101ea056e9fba5ecba0601d"
+ "shas": "89b3d4cd2ef38999c223c69de3011646b1f43c24..82c5ec73355d6296c1bc8e6fbcd9606635930f42"
}
,{
"testCaseDescription": "javascript-array-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/array.js b/array.js",
- "index 3335582..cf37d7c 100644",
+ "index 33355825..cf37d7c1 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" [ \"item1\" ];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "cbf013688399920af101ea056e9fba5ecba0601d..87e3b9ed3c5f26c596ad2b5da90359174c84f53c"
+ "shas": "82c5ec73355d6296c1bc8e6fbcd9606635930f42..2c0dab888be8bb07c850408ff7f3c918c9b2f679"
}
,{
"testCaseDescription": "javascript-array-delete-insert-test",
@@ -120,7 +120,7 @@
],
"patch": [
"diff --git a/array.js b/array.js",
- "index cf37d7c..c2cb17f 100644",
+ "index cf37d7c1..c2cb17fa 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1,3 +1,3 @@",
@@ -130,7 +130,7 @@
" [ \"item1\" ];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "87e3b9ed3c5f26c596ad2b5da90359174c84f53c..ea49177e8ff82b772f7347682975cb1fa5e7b012"
+ "shas": "2c0dab888be8bb07c850408ff7f3c918c9b2f679..2836ffcd06212158191d83c6d23a76b86cd06aa6"
}
,{
"testCaseDescription": "javascript-array-replacement-test",
@@ -161,7 +161,7 @@
],
"patch": [
"diff --git a/array.js b/array.js",
- "index c2cb17f..cf37d7c 100644",
+ "index c2cb17fa..cf37d7c1 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1,3 +1,3 @@",
@@ -171,7 +171,7 @@
" [ \"item1\" ];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ea49177e8ff82b772f7347682975cb1fa5e7b012..1e28fd793a6ab61ed59b28d8ee56b55be7ad79ec"
+ "shas": "2836ffcd06212158191d83c6d23a76b86cd06aa6..6c43843105004658edd13b116c23d3feffc3efb7"
}
,{
"testCaseDescription": "javascript-array-delete-replacement-test",
@@ -232,7 +232,7 @@
],
"patch": [
"diff --git a/array.js b/array.js",
- "index cf37d7c..a4d92b8 100644",
+ "index cf37d7c1..a4d92b81 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1,3 +1,2 @@",
@@ -242,7 +242,7 @@
"+[ \"item1\", \"item2\" ];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1e28fd793a6ab61ed59b28d8ee56b55be7ad79ec..fdc62b5a013932e082ba61a576b8fb54cd1d0791"
+ "shas": "6c43843105004658edd13b116c23d3feffc3efb7..379a870647ba9da2b5faf25da3bd60c6d3983e47"
}
,{
"testCaseDescription": "javascript-array-delete-test",
@@ -273,7 +273,7 @@
],
"patch": [
"diff --git a/array.js b/array.js",
- "index a4d92b8..7f2f50e 100644",
+ "index a4d92b81..7f2f50e6 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1,2 +1 @@",
@@ -281,7 +281,7 @@
" [ \"item1\", \"item2\" ];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "fdc62b5a013932e082ba61a576b8fb54cd1d0791..9e91959fe3d3ec022474f242a8456b900fdfd8d2"
+ "shas": "379a870647ba9da2b5faf25da3bd60c6d3983e47..ca784abe43a28e84e087f70495667e2d0cc5ed77"
}
,{
"testCaseDescription": "javascript-array-delete-rest-test",
@@ -312,12 +312,12 @@
],
"patch": [
"diff --git a/array.js b/array.js",
- "index 7f2f50e..e69de29 100644",
+ "index 7f2f50e6..e69de29b 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1 +0,0 @@",
"-[ \"item1\", \"item2\" ];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9e91959fe3d3ec022474f242a8456b900fdfd8d2..0bdf412036a9a6aea51108a20404c37541fffcfb"
+ "shas": "ca784abe43a28e84e087f70495667e2d0cc5ed77..6a98861e426cf72452392e143d875b8ccd968a2c"
}]
diff --git a/test/corpus/diff-summaries/javascript/arrow-function.json b/test/corpus/diff-summaries/javascript/arrow-function.json
index bd768fce5..e54146d75 100644
--- a/test/corpus/diff-summaries/javascript/arrow-function.json
+++ b/test/corpus/diff-summaries/javascript/arrow-function.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
- "index e69de29..9ef167c 100644",
+ "index e69de29b..9ef167c0 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -0,0 +1 @@",
"+(f, g) => { return h; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d700dc51fee7a3dd557906dcdf46d426285d7955..edda3c60ac532d534d84539648fa827ff18a6c59"
+ "shas": "9adc811773ddcc66050c739b5bc900c4c2daff55..043afc3820510a580d284b7c25a6095675ee1e78"
}
,{
"testCaseDescription": "javascript-arrow-function-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
- "index 9ef167c..92dea6f 100644",
+ "index 9ef167c0..92dea6fa 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" (f, g) => { return h; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "edda3c60ac532d534d84539648fa827ff18a6c59..63fd87f8cafc4a46f2927f9825cc20e5f116a093"
+ "shas": "043afc3820510a580d284b7c25a6095675ee1e78..89e7ef95b30ed04038a529833bc78568279e96c4"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
- "index 92dea6f..8f5bb51 100644",
+ "index 92dea6fa..8f5bb516 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" (f, g) => { return h; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "63fd87f8cafc4a46f2927f9825cc20e5f116a093..29b18be738dde19aa61343c5f4e54bf83f4b30ea"
+ "shas": "89e7ef95b30ed04038a529833bc78568279e96c4..0ca5ab429492655b4558f5ea07ee43e589cd38d9"
}
,{
"testCaseDescription": "javascript-arrow-function-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
- "index 8f5bb51..92dea6f 100644",
+ "index 8f5bb516..92dea6fa 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" (f, g) => { return h; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "29b18be738dde19aa61343c5f4e54bf83f4b30ea..d92f900ef9873f273da632ea9c54adcd7acc7961"
+ "shas": "0ca5ab429492655b4558f5ea07ee43e589cd38d9..5fa58fce48a4fc866783eafd9c774329518a8333"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
- "index 92dea6f..acab9a9 100644",
+ "index 92dea6fa..acab9a9c 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+(f, g) => { return g; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d92f900ef9873f273da632ea9c54adcd7acc7961..243f2be7291992566bd0ab2c2caef9e7ac13e02d"
+ "shas": "5fa58fce48a4fc866783eafd9c774329518a8333..145bae33733e38aa912562a0ad1cacc5a595de17"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
- "index acab9a9..ef1be25 100644",
+ "index acab9a9c..ef1be25b 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" (f, g) => { return g; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "243f2be7291992566bd0ab2c2caef9e7ac13e02d..3128237c6d11459cf7d3e9add902e7be8d38710b"
+ "shas": "145bae33733e38aa912562a0ad1cacc5a595de17..437683161ec5a4d3efcdefde38c4f733402197b5"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
- "index ef1be25..e69de29 100644",
+ "index ef1be25b..e69de29b 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1 +0,0 @@",
"-(f, g) => { return g; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3128237c6d11459cf7d3e9add902e7be8d38710b..5cab8720cde055f6d78f5c5deaf8980b89a434e1"
+ "shas": "437683161ec5a4d3efcdefde38c4f733402197b5..a50f5d25657afa02329debd2a87b7ffbb8f2b76d"
}]
diff --git a/test/corpus/diff-summaries/javascript/assignment.json b/test/corpus/diff-summaries/javascript/assignment.json
index 66519160d..45865dbb7 100644
--- a/test/corpus/diff-summaries/javascript/assignment.json
+++ b/test/corpus/diff-summaries/javascript/assignment.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/assignment.js b/assignment.js",
- "index e69de29..6882fe5 100644",
+ "index e69de29b..6882fe5e 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -0,0 +1 @@",
"+x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "10c888c0caabf36cb211a96640afbe435dfad3fb..6a5eb86577a86881fdd53c3db17dd589617b887e"
+ "shas": "b8e96cb516ef4cd80a86e0b6a00f5d4e542141dd..aa1627d9ad30ddc96644440396be830160280595"
}
,{
"testCaseDescription": "javascript-assignment-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/assignment.js b/assignment.js",
- "index 6882fe5..fb4cba4 100644",
+ "index 6882fe5e..fb4cba44 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6a5eb86577a86881fdd53c3db17dd589617b887e..79ca8610276bd0cc32d257702e20ec268187f1b6"
+ "shas": "aa1627d9ad30ddc96644440396be830160280595..ed0eb692d90f44c893700d15456f02b82c5adb89"
}
,{
"testCaseDescription": "javascript-assignment-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/assignment.js b/assignment.js",
- "index fb4cba4..42e16c6 100644",
+ "index fb4cba44..42e16c61 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "79ca8610276bd0cc32d257702e20ec268187f1b6..c3da25392def8e82aaf0179cdd8cc51849d805c8"
+ "shas": "ed0eb692d90f44c893700d15456f02b82c5adb89..9c07d74d31da21c5ed0bb307a9b11a96e2da6f60"
}
,{
"testCaseDescription": "javascript-assignment-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/assignment.js b/assignment.js",
- "index 42e16c6..fb4cba4 100644",
+ "index 42e16c61..fb4cba44 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c3da25392def8e82aaf0179cdd8cc51849d805c8..be4979757f9464e59b4b7fb7dbdce17f4f362029"
+ "shas": "9c07d74d31da21c5ed0bb307a9b11a96e2da6f60..bb29b11c0519aee4b1469d0510963e5d9f846e97"
}
,{
"testCaseDescription": "javascript-assignment-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/assignment.js b/assignment.js",
- "index fb4cba4..11fe15d 100644",
+ "index fb4cba44..11fe15d7 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "be4979757f9464e59b4b7fb7dbdce17f4f362029..592d4d9a24fe20282bbaa1cf66bbe20959d47ae5"
+ "shas": "bb29b11c0519aee4b1469d0510963e5d9f846e97..daadf6daec7e50a39f21429277fb77556dfc202a"
}
,{
"testCaseDescription": "javascript-assignment-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/assignment.js b/assignment.js",
- "index 11fe15d..198b8f8 100644",
+ "index 11fe15d7..198b8f89 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "592d4d9a24fe20282bbaa1cf66bbe20959d47ae5..f0b77709f5be6c1d671a943d73b8fbb12344762e"
+ "shas": "daadf6daec7e50a39f21429277fb77556dfc202a..f86e9f7675d8d6ad3fb9f6a2703e475b6eb24a8e"
}
,{
"testCaseDescription": "javascript-assignment-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/assignment.js b/assignment.js",
- "index 198b8f8..e69de29 100644",
+ "index 198b8f89..e69de29b 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1 +0,0 @@",
"-x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f0b77709f5be6c1d671a943d73b8fbb12344762e..83f3153b76f49e077237997c965dc6f3c3a159bc"
+ "shas": "f86e9f7675d8d6ad3fb9f6a2703e475b6eb24a8e..8971dc3263a4d4060368d23937d32f6df7c06d16"
}]
diff --git a/test/corpus/diff-summaries/javascript/bitwise-operator.json b/test/corpus/diff-summaries/javascript/bitwise-operator.json
index af2ae33cd..6db5e56bf 100644
--- a/test/corpus/diff-summaries/javascript/bitwise-operator.json
+++ b/test/corpus/diff-summaries/javascript/bitwise-operator.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
- "index e69de29..021cf6a 100644",
+ "index e69de29b..021cf6ad 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -0,0 +1 @@",
"+i >> j;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5edf134e2ccb0fa1cd27b2e07b4279575f1a5f0d..e2e6f5b9a61fa806befb17711cf3ae52dd20f725"
+ "shas": "e94c1e8feb32d2d104b927720bdde792ff068d76..e453aac09a219d4a9bbfc8eb2198ca734ae00e5f"
}
,{
"testCaseDescription": "javascript-bitwise-operator-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
- "index 021cf6a..3e0b6c1 100644",
+ "index 021cf6ad..3e0b6c17 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" i >> j;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "e2e6f5b9a61fa806befb17711cf3ae52dd20f725..de455af0e3ab990d8f20a4555d4bf28324551ed0"
+ "shas": "e453aac09a219d4a9bbfc8eb2198ca734ae00e5f..babfc0072ddedb22fe570ce2954f9a6799436609"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
- "index 3e0b6c1..18853d1 100644",
+ "index 3e0b6c17..18853d16 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" i >> j;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "de455af0e3ab990d8f20a4555d4bf28324551ed0..59f5fd5cc14501c063c3ec3b9563503a4f22537b"
+ "shas": "babfc0072ddedb22fe570ce2954f9a6799436609..eafaa544de1815bbd0cc673d54267631871a450e"
}
,{
"testCaseDescription": "javascript-bitwise-operator-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
- "index 18853d1..3e0b6c1 100644",
+ "index 18853d16..3e0b6c17 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" i >> j;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "59f5fd5cc14501c063c3ec3b9563503a4f22537b..24328d0f069d5e61a5926bedf6e0a074361d7477"
+ "shas": "eafaa544de1815bbd0cc673d54267631871a450e..2b2bac368020ecb0f7c9b891c520a5dfc3ed91a0"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
- "index 3e0b6c1..ee7d8de 100644",
+ "index 3e0b6c17..ee7d8dec 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+i >> k;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "24328d0f069d5e61a5926bedf6e0a074361d7477..083807f60ce4fd39ee7612cb97e2dc2351a09203"
+ "shas": "2b2bac368020ecb0f7c9b891c520a5dfc3ed91a0..30f79b75cc8c70e6ecfdfeeab06764bb85eb333f"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
- "index ee7d8de..2800c8c 100644",
+ "index ee7d8dec..2800c8c8 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" i >> k;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "083807f60ce4fd39ee7612cb97e2dc2351a09203..1bceab9d521db6e74ccfca50dae11d9ac030a4bc"
+ "shas": "30f79b75cc8c70e6ecfdfeeab06764bb85eb333f..c1bb98a01fedb6e04efbe757fea478986c343761"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
- "index 2800c8c..e69de29 100644",
+ "index 2800c8c8..e69de29b 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1 +0,0 @@",
"-i >> k;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1bceab9d521db6e74ccfca50dae11d9ac030a4bc..4e47562dd59646a6c6c55ab138660495394bc5c9"
+ "shas": "c1bb98a01fedb6e04efbe757fea478986c343761..46ec065b158574c8c24c03f95bd0b21ae4388b86"
}]
diff --git a/test/corpus/diff-summaries/javascript/boolean-operator.json b/test/corpus/diff-summaries/javascript/boolean-operator.json
index 7bb818451..e81147d03 100644
--- a/test/corpus/diff-summaries/javascript/boolean-operator.json
+++ b/test/corpus/diff-summaries/javascript/boolean-operator.json
@@ -34,7 +34,7 @@
"+i || j;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "dcb8509973be89c9c4f7239f90bc27b29abe6886..7278cbb3e1324846d217ed8b5d96d30b1d23c9e1"
+ "shas": "68249c6faa764e8f289c3ae7afb4c98267e953d8..3cc5dca41d21643bc3f747a52b88c31e6563d6ed"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-insert-test",
@@ -89,7 +89,7 @@
" i || j;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7278cbb3e1324846d217ed8b5d96d30b1d23c9e1..dcbb69024b9472b7573c1284b9f2a9ba3c0bf241"
+ "shas": "3cc5dca41d21643bc3f747a52b88c31e6563d6ed..48f0f67eaa06dba7fc3c8f381f380b23e171cd43"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-insert-test",
@@ -142,7 +142,7 @@
" i || j;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "dcbb69024b9472b7573c1284b9f2a9ba3c0bf241..1d4a46d71e3418079b81f3b494ead0ddec0770ef"
+ "shas": "48f0f67eaa06dba7fc3c8f381f380b23e171cd43..253a952891f8ab38a872a1544b27d7372b223bcb"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-test",
@@ -195,7 +195,7 @@
" i || j;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1d4a46d71e3418079b81f3b494ead0ddec0770ef..59bf7426522f2e5a40fd2fbd5e9adc595c4a6f26"
+ "shas": "253a952891f8ab38a872a1544b27d7372b223bcb..6cfd731b9477f9b2c190e140a112ecf6854b4bef"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-replacement-test",
@@ -266,7 +266,7 @@
"+i && j;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "59bf7426522f2e5a40fd2fbd5e9adc595c4a6f26..2aff614351987457ce3a0ce900610cf622e1765e"
+ "shas": "6cfd731b9477f9b2c190e140a112ecf6854b4bef..c7af49d44705dcf8ee38e13159ddc09eea64f683"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-test",
@@ -305,7 +305,7 @@
" i && j;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2aff614351987457ce3a0ce900610cf622e1765e..df4a601cd0eea4d8db63a7f7097753ae9fbd9f4b"
+ "shas": "c7af49d44705dcf8ee38e13159ddc09eea64f683..47df410d73472fbeb7cf2ebef0d6f21096395e51"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-rest-test",
@@ -343,5 +343,5 @@
"-i && j;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "df4a601cd0eea4d8db63a7f7097753ae9fbd9f4b..1d234a84ee270c0d6a329fcdcbc065e50bed813b"
+ "shas": "47df410d73472fbeb7cf2ebef0d6f21096395e51..e94c1e8feb32d2d104b927720bdde792ff068d76"
}]
diff --git a/test/corpus/diff-summaries/javascript/break.json b/test/corpus/diff-summaries/javascript/break.json
index d75a4e8b0..2cbe925e4 100644
--- a/test/corpus/diff-summaries/javascript/break.json
+++ b/test/corpus/diff-summaries/javascript/break.json
@@ -34,7 +34,7 @@
"+for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0e81c586bea55e0eeb46e3422b25ccba96c7d9ea..d86036d38621253021f5fde6256a16a5d58ffd49"
+ "shas": "7b8267eabe246347b009d08c9100f36a568a81a6..28130e2a01e50fed72c5d18d6ccd586431a83bfc"
}
,{
"testCaseDescription": "javascript-break-insert-test",
@@ -88,7 +88,7 @@
"+for (i = 0; i < 10; i++) { if (i === 4) { break; }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d86036d38621253021f5fde6256a16a5d58ffd49..c2a0cadf8477ba2c7525fba7c37923afd994ad15"
+ "shas": "28130e2a01e50fed72c5d18d6ccd586431a83bfc..317d999d5da052390013abf0f427fd789c566257"
}
,{
"testCaseDescription": "javascript-break-replacement-test",
@@ -142,7 +142,7 @@
"+for (i = 0; i < 10; i++) { if (i === 4) { continue; }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c2a0cadf8477ba2c7525fba7c37923afd994ad15..3bcd48f5d5894250de6349c4ca5272b3ae92fa6d"
+ "shas": "317d999d5da052390013abf0f427fd789c566257..9fe6a556575e0705efd0de4d67f1868e143e16d0"
}
,{
"testCaseDescription": "javascript-break-delete-replacement-test",
@@ -196,7 +196,7 @@
"+for (i = 0; i < 10; i++) { if (i === 4) { break; }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3bcd48f5d5894250de6349c4ca5272b3ae92fa6d..bbabc7d7ad65f9ab05f74f83c6e5777a3eeb4be2"
+ "shas": "9fe6a556575e0705efd0de4d67f1868e143e16d0..7ecb84d91df841eddd510ab0c991ae5ca71b69f6"
}
,{
"testCaseDescription": "javascript-break-delete-insert-test",
@@ -250,7 +250,7 @@
"+for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "bbabc7d7ad65f9ab05f74f83c6e5777a3eeb4be2..016996f57081dda9f5b4ebdd801853944017b617"
+ "shas": "7ecb84d91df841eddd510ab0c991ae5ca71b69f6..2d0483e720373f442c34a5f9c1a097c6a318a7d8"
}
,{
"testCaseDescription": "javascript-break-teardown-test",
@@ -288,5 +288,5 @@
"-for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "016996f57081dda9f5b4ebdd801853944017b617..7b31459c5a9378f4fe26f4e3e6d5c1fd3b6aee23"
+ "shas": "2d0483e720373f442c34a5f9c1a097c6a318a7d8..d0acf2e1ee4c3ff99054d1cd40885f62e64b87be"
}]
diff --git a/test/corpus/diff-summaries/javascript/chained-callbacks.json b/test/corpus/diff-summaries/javascript/chained-callbacks.json
index 253a7cb57..b8421d915 100644
--- a/test/corpus/diff-summaries/javascript/chained-callbacks.json
+++ b/test/corpus/diff-summaries/javascript/chained-callbacks.json
@@ -16,7 +16,7 @@
]
}
},
- "summary": "Added the 'this.map(…)' method call"
+ "summary": "Added the 'this.map(…)' function call"
}
]
},
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
- "index e69de29..ce9ee1e 100644",
+ "index e69de29b..ce9ee1ed 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -0,0 +1 @@",
"+this.map(function (a) { return a.b; })"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1512ae1cef2a096ce2723ce98334e4ce0e4bc82b..2a014ee8fd6ea4f8ce5b6bae0ca35a4fa6462deb"
+ "shas": "e97f568708cabfc40035c206b04bf5b6abf6e5bd..f14828a645c440584da5db2b188a4155d63843e0"
}
,{
"testCaseDescription": "javascript-chained-callbacks-replacement-insert-test",
@@ -54,7 +54,7 @@
]
}
},
- "summary": "Added the 'this.reduce(…)' method call"
+ "summary": "Added the 'this.reduce(…)' function call"
},
{
"span": {
@@ -69,7 +69,7 @@
]
}
},
- "summary": "Added the 'this.map(…)' method call"
+ "summary": "Added the 'this.map(…)' function call"
}
]
},
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
- "index ce9ee1e..acba744 100644",
+ "index ce9ee1ed..acba744a 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" this.map(function (a) { return a.b; })"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2a014ee8fd6ea4f8ce5b6bae0ca35a4fa6462deb..6a6e1ae99abc9cae5f8ac31aac43836380944603"
+ "shas": "f14828a645c440584da5db2b188a4155d63843e0..861d17aed5329b7a49e2f97ae261307fe9b4431e"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-insert-test",
@@ -121,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'reduce' identifier with the 'map' identifier in the this.map(…) method call"
+ "summary": "Replaced the 'reduce' identifier with the 'map' identifier in the this.map(…) function call"
},
{
"span": {
@@ -148,7 +148,7 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.map(…) method call"
+ "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.map(…) function call"
},
{
"span": {
@@ -175,7 +175,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.map(…) method call"
+ "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.map(…) function call"
}
]
},
@@ -186,7 +186,7 @@
],
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
- "index acba744..7390534 100644",
+ "index acba744a..73905343 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1,3 +1,3 @@",
@@ -196,7 +196,7 @@
" this.map(function (a) { return a.b; })"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6a6e1ae99abc9cae5f8ac31aac43836380944603..c86429cb689c74e2ce3988c8bc257a365734cbe3"
+ "shas": "861d17aed5329b7a49e2f97ae261307fe9b4431e..e2193800198a04799244dc9f70907be929bdc41f"
}
,{
"testCaseDescription": "javascript-chained-callbacks-replacement-test",
@@ -228,7 +228,7 @@
}
]
},
- "summary": "Replaced the 'map' identifier with the 'reduce' identifier in the this.reduce(…) method call"
+ "summary": "Replaced the 'map' identifier with the 'reduce' identifier in the this.reduce(…) function call"
},
{
"span": {
@@ -255,7 +255,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.reduce(…) method call"
+ "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.reduce(…) function call"
},
{
"span": {
@@ -282,7 +282,7 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.reduce(…) method call"
+ "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.reduce(…) function call"
}
]
},
@@ -293,7 +293,7 @@
],
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
- "index 7390534..acba744 100644",
+ "index 73905343..acba744a 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1,3 +1,3 @@",
@@ -303,7 +303,7 @@
" this.map(function (a) { return a.b; })"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c86429cb689c74e2ce3988c8bc257a365734cbe3..c4df0b8afdd73cae6d89a9098ae38d9c3085dbb8"
+ "shas": "e2193800198a04799244dc9f70907be929bdc41f..53dec994d0dc3b7c7bcc9249cab85a543ef25200"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-replacement-test",
@@ -323,7 +323,7 @@
]
}
},
- "summary": "Deleted the 'this.reduce(…)' method call"
+ "summary": "Deleted the 'this.reduce(…)' function call"
},
{
"span": {
@@ -338,7 +338,7 @@
]
}
},
- "summary": "Deleted the 'this.map(…)' method call"
+ "summary": "Deleted the 'this.map(…)' function call"
},
{
"span": {
@@ -353,7 +353,7 @@
]
}
},
- "summary": "Added the 'this.reduce(…)' method call"
+ "summary": "Added the 'this.reduce(…)' function call"
}
]
},
@@ -364,7 +364,7 @@
],
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
- "index acba744..c4db432 100644",
+ "index acba744a..c4db4326 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1,3 +1,2 @@",
@@ -374,7 +374,7 @@
"+this.reduce(function (a) { return b.a; })"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c4df0b8afdd73cae6d89a9098ae38d9c3085dbb8..8b7dbbb0ca20e47dfed24fb3eb3a790721d2e9d0"
+ "shas": "53dec994d0dc3b7c7bcc9249cab85a543ef25200..294233550240c3b5f5b279f688cc1f0dd2416ceb"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-test",
@@ -394,7 +394,7 @@
]
}
},
- "summary": "Deleted the 'this.map(…)' method call"
+ "summary": "Deleted the 'this.map(…)' function call"
}
]
},
@@ -405,7 +405,7 @@
],
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
- "index c4db432..e593419 100644",
+ "index c4db4326..e5934198 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1,2 +1 @@",
@@ -413,7 +413,7 @@
" this.reduce(function (a) { return b.a; })"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8b7dbbb0ca20e47dfed24fb3eb3a790721d2e9d0..e2c2e86db834a0ab3c6006c6385e90d780851357"
+ "shas": "294233550240c3b5f5b279f688cc1f0dd2416ceb..bc7658e860c11b717d322c7c38b7b5be70af8169"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-rest-test",
@@ -433,7 +433,7 @@
]
}
},
- "summary": "Deleted the 'this.reduce(…)' method call"
+ "summary": "Deleted the 'this.reduce(…)' function call"
}
]
},
@@ -444,12 +444,12 @@
],
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
- "index e593419..e69de29 100644",
+ "index e5934198..e69de29b 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1 +0,0 @@",
"-this.reduce(function (a) { return b.a; })"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "e2c2e86db834a0ab3c6006c6385e90d780851357..5ef42771e35b5af39f3befe137fedf40f174a5c7"
+ "shas": "bc7658e860c11b717d322c7c38b7b5be70af8169..65ec4b91fc50d92244f898493564425dc91dec99"
}]
diff --git a/test/corpus/diff-summaries/javascript/chained-property-access.json b/test/corpus/diff-summaries/javascript/chained-property-access.json
index bffd5f342..52665ed4f 100644
--- a/test/corpus/diff-summaries/javascript/chained-property-access.json
+++ b/test/corpus/diff-summaries/javascript/chained-property-access.json
@@ -34,7 +34,7 @@
"+return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b4a1b602905b005b1bfe48d8f78faebd8c9cf016..e4dd7ea96606956464809e9a3bcfdb81f318c39b"
+ "shas": "c0d1f59dbc88b8a161e9dfa867107276f10b2898..b8c22790764e8661eb7f8d764e9b0af1b93cdd89"
}
,{
"testCaseDescription": "javascript-chained-property-access-replacement-insert-test",
@@ -89,7 +89,7 @@
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "e4dd7ea96606956464809e9a3bcfdb81f318c39b..6365577e012aa898ba1d2cc77d10eec1fb9a016d"
+ "shas": "b8c22790764e8661eb7f8d764e9b0af1b93cdd89..63a6ea11f36663237346e70a138fd62524b9aef6"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-insert-test",
@@ -121,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…) method call"
+ "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…) function call"
},
{
"span": {
@@ -148,7 +148,7 @@
}
]
},
- "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…).fail(…) method call"
+ "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…).fail(…) function call"
}
]
},
@@ -169,7 +169,7 @@
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6365577e012aa898ba1d2cc77d10eec1fb9a016d..8ab9cd6c506847581b2fc7f04124803cd344b3ff"
+ "shas": "63a6ea11f36663237346e70a138fd62524b9aef6..1bbcdcf73d6865d9695b99b229ac793f118439a4"
}
,{
"testCaseDescription": "javascript-chained-property-access-replacement-test",
@@ -201,7 +201,7 @@
}
]
},
- "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…) method call"
+ "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…) function call"
},
{
"span": {
@@ -228,7 +228,7 @@
}
]
},
- "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…).fail(…) method call"
+ "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…).fail(…) function call"
}
]
},
@@ -249,7 +249,7 @@
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8ab9cd6c506847581b2fc7f04124803cd344b3ff..d535074522aa956a8ea7e8d943227d9d78775725"
+ "shas": "1bbcdcf73d6865d9695b99b229ac793f118439a4..6b89d7a2b0d652938ed2c5f638d5091c6d8555d2"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-replacement-test",
@@ -320,7 +320,7 @@
"+return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d535074522aa956a8ea7e8d943227d9d78775725..b3f90f50ba0ea4d42e78ba37c176a4d69282fcd7"
+ "shas": "6b89d7a2b0d652938ed2c5f638d5091c6d8555d2..99c802ed801ddf5a24e177c5a08fc18f2658c6ce"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-test",
@@ -359,7 +359,7 @@
" return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b3f90f50ba0ea4d42e78ba37c176a4d69282fcd7..6dd90e85a905d3c205cd42bcbedaa3d50110d426"
+ "shas": "99c802ed801ddf5a24e177c5a08fc18f2658c6ce..6b0b1796a40ecd246a53b69ffa84e15966547ff9"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-rest-test",
@@ -397,5 +397,5 @@
"-return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6dd90e85a905d3c205cd42bcbedaa3d50110d426..7b26c97829302e6f2c2fc76d9a1e5dc25caf58d9"
+ "shas": "6b0b1796a40ecd246a53b69ffa84e15966547ff9..e97f568708cabfc40035c206b04bf5b6abf6e5bd"
}]
diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json
index ab4c4cfe2..5fb17956a 100644
--- a/test/corpus/diff-summaries/javascript/class.json
+++ b/test/corpus/diff-summaries/javascript/class.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/class.js b/class.js",
- "index e69de29..8f6ae64 100644",
+ "index e69de29b..8f6ae64d 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",
- "shas": "f6dfeb42af9db740677fd60341ea39da711f7c81..f071d25d12bb0086a285449efbe5cfaeeed8e436"
+ "shas": "d9d6e19c015a3f2dbb9d04d3867b13889dd798ac..05fc0916c3ad9408a0e1b0fd90bb83d43628e892"
}
,{
"testCaseDescription": "javascript-class-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/class.js b/class.js",
- "index 8f6ae64..b509437 100644",
+ "index 8f6ae64d..b509437f 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f071d25d12bb0086a285449efbe5cfaeeed8e436..ba736a07888eb4991323c035f2bf78fe1650ea56"
+ "shas": "05fc0916c3ad9408a0e1b0fd90bb83d43628e892..4204d9bb3c5c1cfab6dc2b6af925b0666d015cb0"
}
,{
"testCaseDescription": "javascript-class-delete-insert-test",
@@ -192,7 +192,7 @@
],
"patch": [
"diff --git a/class.js b/class.js",
- "index b509437..c4f5c91 100644",
+ "index b509437f..c4f5c91c 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -1,3 +1,3 @@",
@@ -202,7 +202,7 @@
" class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ba736a07888eb4991323c035f2bf78fe1650ea56..c99d7b8dc9cff808ef1e6010caa4573ad1694d9b"
+ "shas": "4204d9bb3c5c1cfab6dc2b6af925b0666d015cb0..18b9de02fda94811dad14657d61160c8943b6576"
}
,{
"testCaseDescription": "javascript-class-replacement-test",
@@ -305,7 +305,7 @@
],
"patch": [
"diff --git a/class.js b/class.js",
- "index c4f5c91..b509437 100644",
+ "index c4f5c91c..b509437f 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -1,3 +1,3 @@",
@@ -315,7 +315,7 @@
" class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c99d7b8dc9cff808ef1e6010caa4573ad1694d9b..75a0caa880f62a0706ff723f555a9ec1f0c53c29"
+ "shas": "18b9de02fda94811dad14657d61160c8943b6576..c4c35843b5c7aa3d018d196d8fb86f2495b7881c"
}
,{
"testCaseDescription": "javascript-class-delete-replacement-test",
@@ -376,7 +376,7 @@
],
"patch": [
"diff --git a/class.js b/class.js",
- "index b509437..b1ef404 100644",
+ "index b509437f..b1ef404f 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -1,3 +1,2 @@",
@@ -386,7 +386,7 @@
"+class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "75a0caa880f62a0706ff723f555a9ec1f0c53c29..4231a3b306d145aa37ceb879ef6f8da6221e54b8"
+ "shas": "c4c35843b5c7aa3d018d196d8fb86f2495b7881c..af0a7a4e55d3b67109f4455766d91410a6113c76"
}
,{
"testCaseDescription": "javascript-class-delete-test",
@@ -417,7 +417,7 @@
],
"patch": [
"diff --git a/class.js b/class.js",
- "index b1ef404..2c17f72 100644",
+ "index b1ef404f..2c17f72f 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -1,2 +1 @@",
@@ -425,7 +425,7 @@
" class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4231a3b306d145aa37ceb879ef6f8da6221e54b8..d5627235989da4028cfcb15c4b1ee2bdc544fd31"
+ "shas": "af0a7a4e55d3b67109f4455766d91410a6113c76..417e7b1dc2606c4235a0fecf05b8d1c3c170f661"
}
,{
"testCaseDescription": "javascript-class-delete-rest-test",
@@ -456,12 +456,12 @@
],
"patch": [
"diff --git a/class.js b/class.js",
- "index 2c17f72..e69de29 100644",
+ "index 2c17f72f..e69de29b 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",
- "shas": "d5627235989da4028cfcb15c4b1ee2bdc544fd31..654a538b26c9b4c8637e6c2e4cd497c93e690310"
+ "shas": "417e7b1dc2606c4235a0fecf05b8d1c3c170f661..89b3d4cd2ef38999c223c69de3011646b1f43c24"
}]
diff --git a/test/corpus/diff-summaries/javascript/comma-operator.json b/test/corpus/diff-summaries/javascript/comma-operator.json
index 66a418dab..c2c5791c1 100644
--- a/test/corpus/diff-summaries/javascript/comma-operator.json
+++ b/test/corpus/diff-summaries/javascript/comma-operator.json
@@ -42,14 +42,14 @@
],
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
- "index e69de29..cff019f 100644",
+ "index e69de29b..cff019f3 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -0,0 +1 @@",
"+a = 1, b = 2;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ec86aaba01801d01aca70fd31403642be1e2d438..b0a5f928a8a4594bb176a56275c43ccab6e2e2a0"
+ "shas": "a51b44e93b10645f205b119e37a93f384ee4d64c..ac141d1975c9e286bd16621b4b3ae94bb090d770"
}
,{
"testCaseDescription": "javascript-comma-operator-replacement-insert-test",
@@ -110,7 +110,7 @@
],
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
- "index cff019f..93ece10 100644",
+ "index cff019f3..93ece10f 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1 +1,3 @@",
@@ -119,7 +119,7 @@
" a = 1, b = 2;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b0a5f928a8a4594bb176a56275c43ccab6e2e2a0..315b46ccdb9a45c374b4ed1cc51a062d74c13a78"
+ "shas": "ac141d1975c9e286bd16621b4b3ae94bb090d770..78f0ad9203b9d8f4a9265f3187898608a6b7b22a"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-insert-test",
@@ -180,7 +180,7 @@
],
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
- "index 93ece10..f738c2d 100644",
+ "index 93ece10f..f738c2db 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1,3 +1,3 @@",
@@ -190,7 +190,7 @@
" a = 1, b = 2;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "315b46ccdb9a45c374b4ed1cc51a062d74c13a78..30cf69eb0cc5543fe53be82f29cd0e0371e30cd1"
+ "shas": "78f0ad9203b9d8f4a9265f3187898608a6b7b22a..ef480cfe1b76305d27d2601402153b0c1db0a8c6"
}
,{
"testCaseDescription": "javascript-comma-operator-replacement-test",
@@ -251,7 +251,7 @@
],
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
- "index f738c2d..93ece10 100644",
+ "index f738c2db..93ece10f 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1,3 +1,3 @@",
@@ -261,7 +261,7 @@
" a = 1, b = 2;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "30cf69eb0cc5543fe53be82f29cd0e0371e30cd1..a454c132f64a253a51cbf1a1455e74fca9343c23"
+ "shas": "ef480cfe1b76305d27d2601402153b0c1db0a8c6..7040e05f7443780ecfd99ae3c2a6bf0f62a9c9c3"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-replacement-test",
@@ -337,7 +337,7 @@
],
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
- "index 93ece10..297e28d 100644",
+ "index 93ece10f..297e28dd 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1,3 +1,2 @@",
@@ -347,7 +347,7 @@
"+c = {d: (3, 4 + 5, 6)};"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "a454c132f64a253a51cbf1a1455e74fca9343c23..db24ea61ad00e73c91b0a4b616f333a5eac48f29"
+ "shas": "7040e05f7443780ecfd99ae3c2a6bf0f62a9c9c3..1733573e2a24dd8395474b1fbe2ffbf73a129dcb"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-test",
@@ -393,7 +393,7 @@
],
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
- "index 297e28d..421bc7f 100644",
+ "index 297e28dd..421bc7fe 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1,2 +1 @@",
@@ -401,7 +401,7 @@
" c = {d: (3, 4 + 5, 6)};"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "db24ea61ad00e73c91b0a4b616f333a5eac48f29..4ec8128c2ab11f7bf00c002d0fec6c8601b14c16"
+ "shas": "1733573e2a24dd8395474b1fbe2ffbf73a129dcb..94c3384b441a218b1720ef3c6934e69c172d938d"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-rest-test",
@@ -432,12 +432,12 @@
],
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
- "index 421bc7f..e69de29 100644",
+ "index 421bc7fe..e69de29b 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1 +0,0 @@",
"-c = {d: (3, 4 + 5, 6)};"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4ec8128c2ab11f7bf00c002d0fec6c8601b14c16..0ccf8092231ebc8ac92cc60fe614f1681bc03a89"
+ "shas": "94c3384b441a218b1720ef3c6934e69c172d938d..4e62b822a53dcb5dd4c87ffe6ce9db53015fdc68"
}]
diff --git a/test/corpus/diff-summaries/javascript/comment.json b/test/corpus/diff-summaries/javascript/comment.json
index a1ba7d82b..4ea5bc8fd 100644
--- a/test/corpus/diff-summaries/javascript/comment.json
+++ b/test/corpus/diff-summaries/javascript/comment.json
@@ -9,14 +9,14 @@
],
"patch": [
"diff --git a/comment.js b/comment.js",
- "index e69de29..a5821d2 100644",
+ "index e69de29b..a5821d24 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -0,0 +1 @@",
"+// This is a property"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "81bc4513ad3979452e9e95586a5fbc9ca66eeadc..522a93132b55605393a0f7a5421f3d1f7b0d4a8c"
+ "shas": "56b3ef654938c8fc1c02e365cb518f170511a823..9330732da3f60c8e6437c4d11d79aed78a791b04"
}
,{
"testCaseDescription": "javascript-comment-replacement-insert-test",
@@ -29,7 +29,7 @@
],
"patch": [
"diff --git a/comment.js b/comment.js",
- "index a5821d2..761aa7a 100644",
+ "index a5821d24..761aa7a3 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1 +1,5 @@",
@@ -40,7 +40,7 @@
" // This is a property"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "522a93132b55605393a0f7a5421f3d1f7b0d4a8c..f0aa09e8712b14d61160b16073cac5fbd0276038"
+ "shas": "9330732da3f60c8e6437c4d11d79aed78a791b04..c08e371085c5af8d5e11d734ba46ffbbc4d8edbf"
}
,{
"testCaseDescription": "javascript-comment-delete-insert-test",
@@ -53,7 +53,7 @@
],
"patch": [
"diff --git a/comment.js b/comment.js",
- "index 761aa7a..3b33406 100644",
+ "index 761aa7a3..3b33406a 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1,5 +1,3 @@",
@@ -65,7 +65,7 @@
" // This is a property"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f0aa09e8712b14d61160b16073cac5fbd0276038..9402b254de81dabcddcbd6d7308911822b6f0f59"
+ "shas": "c08e371085c5af8d5e11d734ba46ffbbc4d8edbf..2f680ffad4edd7e2631d6b2a03d73a6f9ed66813"
}
,{
"testCaseDescription": "javascript-comment-replacement-test",
@@ -78,7 +78,7 @@
],
"patch": [
"diff --git a/comment.js b/comment.js",
- "index 3b33406..761aa7a 100644",
+ "index 3b33406a..761aa7a3 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1,3 +1,5 @@",
@@ -90,7 +90,7 @@
" // This is a property"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9402b254de81dabcddcbd6d7308911822b6f0f59..ba788116c40403584cd03df9976350810a9b1162"
+ "shas": "2f680ffad4edd7e2631d6b2a03d73a6f9ed66813..95bdc17204a7e6522cbf0dd0e985cd35865c6f7d"
}
,{
"testCaseDescription": "javascript-comment-delete-replacement-test",
@@ -103,7 +103,7 @@
],
"patch": [
"diff --git a/comment.js b/comment.js",
- "index 761aa7a..c2a8148 100644",
+ "index 761aa7a3..c2a8148a 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1,5 +1,4 @@",
@@ -115,7 +115,7 @@
"-// This is a property"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ba788116c40403584cd03df9976350810a9b1162..05a2041be1630b8a7309163d4b863cd8966adbe0"
+ "shas": "95bdc17204a7e6522cbf0dd0e985cd35865c6f7d..22fae60a84e7c276dac1afcb316a72a7ae530c37"
}
,{
"testCaseDescription": "javascript-comment-delete-test",
@@ -128,7 +128,7 @@
],
"patch": [
"diff --git a/comment.js b/comment.js",
- "index c2a8148..7c74dcd 100644",
+ "index c2a8148a..7c74dcdf 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1,4 +1,3 @@",
@@ -138,7 +138,7 @@
" */"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "05a2041be1630b8a7309163d4b863cd8966adbe0..28ae9fb48ab99b60a709d3168a82f53017fa27a0"
+ "shas": "22fae60a84e7c276dac1afcb316a72a7ae530c37..6273138826febf9dd2611fcb51bb643606b284be"
}
,{
"testCaseDescription": "javascript-comment-delete-rest-test",
@@ -151,7 +151,7 @@
],
"patch": [
"diff --git a/comment.js b/comment.js",
- "index 7c74dcd..e69de29 100644",
+ "index 7c74dcdf..e69de29b 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1,3 +0,0 @@",
@@ -160,5 +160,5 @@
"-*/"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "28ae9fb48ab99b60a709d3168a82f53017fa27a0..8f7edd21ecef61769b82fb5a60a881f31ce30a01"
+ "shas": "6273138826febf9dd2611fcb51bb643606b284be..20109cf62d65353fadfe9965edbf1f9e875db9c4"
}]
diff --git a/test/corpus/diff-summaries/javascript/constructor-call.json b/test/corpus/diff-summaries/javascript/constructor-call.json
index 98781ff1c..2cdbc3b0a 100644
--- a/test/corpus/diff-summaries/javascript/constructor-call.json
+++ b/test/corpus/diff-summaries/javascript/constructor-call.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
- "index e69de29..9d723b9 100644",
+ "index e69de29b..9d723b91 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -0,0 +1 @@",
"+new module.Klass(1, \"two\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b1ed87edc6bf561edc524058ab781a95970a3258..692f777ed1db0b3284bd2728f6c651425e20ab34"
+ "shas": "bc8f6203c7c5033d706c0155313d250aff41b6ce..3caf8ac9c67ede5f4ca73fa8f4ce3fd50f5b4760"
}
,{
"testCaseDescription": "javascript-constructor-call-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
- "index 9d723b9..2c91b11 100644",
+ "index 9d723b91..2c91b115 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" new module.Klass(1, \"two\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "692f777ed1db0b3284bd2728f6c651425e20ab34..e4d96364ed5caab5be836020193ea527a6cd6e55"
+ "shas": "3caf8ac9c67ede5f4ca73fa8f4ce3fd50f5b4760..2e8198e081b41db8e2acbf111fe27f6ad6485cb5"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-insert-test",
@@ -121,7 +121,7 @@
}
]
},
- "summary": "Replaced the \"three\" string with the \"two\" string in the module.Klass(1, \"two\") method call"
+ "summary": "Replaced the \"three\" string with the \"two\" string in the module.Klass(1, \"two\") function call"
}
]
},
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
- "index 2c91b11..892f542 100644",
+ "index 2c91b115..892f5425 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" new module.Klass(1, \"two\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "e4d96364ed5caab5be836020193ea527a6cd6e55..c5f5c7389717f787423d9698a3e0593a965ffbd5"
+ "shas": "2e8198e081b41db8e2acbf111fe27f6ad6485cb5..8b2e189f8eadc258f196519389b45657f5067553"
}
,{
"testCaseDescription": "javascript-constructor-call-replacement-test",
@@ -174,7 +174,7 @@
}
]
},
- "summary": "Replaced the \"two\" string with the \"three\" string in the module.Klass(1, \"three\") method call"
+ "summary": "Replaced the \"two\" string with the \"three\" string in the module.Klass(1, \"three\") function call"
}
]
},
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
- "index 892f542..2c91b11 100644",
+ "index 892f5425..2c91b115 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" new module.Klass(1, \"two\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c5f5c7389717f787423d9698a3e0593a965ffbd5..d17799b023d4e85c6e1d97220121da96a1323970"
+ "shas": "8b2e189f8eadc258f196519389b45657f5067553..27f7005c773c3ace00b6f45987dfd72b9afa8144"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
- "index 2c91b11..cd77b98 100644",
+ "index 2c91b115..cd77b985 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+new module.Klass(1, \"three\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d17799b023d4e85c6e1d97220121da96a1323970..ddc3d491ed287b5aee714bedf5c2de5ba46770ce"
+ "shas": "27f7005c773c3ace00b6f45987dfd72b9afa8144..c9a6ceeda21a46940f061c9a31e10160cfafa5bf"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
- "index cd77b98..75f6a29 100644",
+ "index cd77b985..75f6a29e 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" new module.Klass(1, \"three\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ddc3d491ed287b5aee714bedf5c2de5ba46770ce..e0a37e9237220e1382c4502fdfbbb4cc10cf04e0"
+ "shas": "c9a6ceeda21a46940f061c9a31e10160cfafa5bf..d4e43daedb1bb2589ec006729907f9ed22855eb4"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
- "index 75f6a29..e69de29 100644",
+ "index 75f6a29e..e69de29b 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1 +0,0 @@",
"-new module.Klass(1, \"three\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "e0a37e9237220e1382c4502fdfbbb4cc10cf04e0..41ab7cb7dc378bf229f7a08f1a03c0676483f435"
+ "shas": "d4e43daedb1bb2589ec006729907f9ed22855eb4..6c2a6d2038e58ffec3265d64973449c3c258d5ad"
}]
diff --git a/test/corpus/diff-summaries/javascript/continue.json b/test/corpus/diff-summaries/javascript/continue.json
index 6c27bf216..46db2255f 100644
--- a/test/corpus/diff-summaries/javascript/continue.json
+++ b/test/corpus/diff-summaries/javascript/continue.json
@@ -34,7 +34,7 @@
"+for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7b31459c5a9378f4fe26f4e3e6d5c1fd3b6aee23..6f1f37c267e2d029c289f0fbcf27091ba3d1dec0"
+ "shas": "d0acf2e1ee4c3ff99054d1cd40885f62e64b87be..e462b8742bc8299068fb433b43f25f19052e7ded"
}
,{
"testCaseDescription": "javascript-continue-insert-test",
@@ -88,7 +88,7 @@
"+for (i = 0; i < 10; i++) { if (i === 4) { continue; }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6f1f37c267e2d029c289f0fbcf27091ba3d1dec0..b23c299b2611ac212c2f335a44e9ffcfbe821ed4"
+ "shas": "e462b8742bc8299068fb433b43f25f19052e7ded..53af971a479c713135ccf4d7e465f939604bbb6d"
}
,{
"testCaseDescription": "javascript-continue-replacement-test",
@@ -142,7 +142,7 @@
"+for (i = 0; i < 10; i++) { if (i === 4) { break; }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b23c299b2611ac212c2f335a44e9ffcfbe821ed4..59f5084383702801c670c2d9738a4d78c93a0b0a"
+ "shas": "53af971a479c713135ccf4d7e465f939604bbb6d..6bb94227de7471638516c4c9f9dde95c4b09f9b1"
}
,{
"testCaseDescription": "javascript-continue-delete-replacement-test",
@@ -196,7 +196,7 @@
"+for (i = 0; i < 10; i++) { if (i === 4) { continue; }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "59f5084383702801c670c2d9738a4d78c93a0b0a..ac045f406aaa05c9c85d6a20e527e2e62e99ce2c"
+ "shas": "6bb94227de7471638516c4c9f9dde95c4b09f9b1..de9c6f44f672d452e72d7071ec536ee6de076efd"
}
,{
"testCaseDescription": "javascript-continue-delete-insert-test",
@@ -250,7 +250,7 @@
"+for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ac045f406aaa05c9c85d6a20e527e2e62e99ce2c..0c96f2e07ccf5ac404d4301a1a1e5ca9aa19b0b3"
+ "shas": "de9c6f44f672d452e72d7071ec536ee6de076efd..49f94303b4c1ce4ec4b1d17b5dae99264c690b82"
}
,{
"testCaseDescription": "javascript-continue-teardown-test",
@@ -288,5 +288,5 @@
"-for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0c96f2e07ccf5ac404d4301a1a1e5ca9aa19b0b3..b4a1b602905b005b1bfe48d8f78faebd8c9cf016"
+ "shas": "49f94303b4c1ce4ec4b1d17b5dae99264c690b82..5e76eb9bd80785120da1d03a39846954694b0a87"
}]
diff --git a/test/corpus/diff-summaries/javascript/delete-operator.json b/test/corpus/diff-summaries/javascript/delete-operator.json
index d134089b9..93f2c4fd6 100644
--- a/test/corpus/diff-summaries/javascript/delete-operator.json
+++ b/test/corpus/diff-summaries/javascript/delete-operator.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
- "index e69de29..c83346d 100644",
+ "index e69de29b..c83346db 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -0,0 +1 @@",
"+delete thing['prop'];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b5645de0a9c0002d8f44d302c200dd88ff113f52..d1aaae4cff971b6bd6647c77427eab5789728dea"
+ "shas": "40c56c88e1737aa2249e65bf6883ae636953376f..ee79dec332e4b19b503a3ffb045b1a62a316b947"
}
,{
"testCaseDescription": "javascript-delete-operator-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
- "index c83346d..7c8b990 100644",
+ "index c83346db..7c8b9908 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" delete thing['prop'];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d1aaae4cff971b6bd6647c77427eab5789728dea..6444b777c04540c4e0229617aaadcf274dbe092f"
+ "shas": "ee79dec332e4b19b503a3ffb045b1a62a316b947..a6f1cfe9edeaf12c99653aeaf65488509b500b4b"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
- "index 7c8b990..f506e36 100644",
+ "index 7c8b9908..f506e360 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" delete thing['prop'];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6444b777c04540c4e0229617aaadcf274dbe092f..ce69f237ff3cf767d8814435ffa957dadfeafa37"
+ "shas": "a6f1cfe9edeaf12c99653aeaf65488509b500b4b..bc0464b08e597fe9799ba5c4dcd8790cee637929"
}
,{
"testCaseDescription": "javascript-delete-operator-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
- "index f506e36..7c8b990 100644",
+ "index f506e360..7c8b9908 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" delete thing['prop'];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ce69f237ff3cf767d8814435ffa957dadfeafa37..71f7d6db03225cbfcc31f2bbd6ab589e9183c55c"
+ "shas": "bc0464b08e597fe9799ba5c4dcd8790cee637929..c001371459eed13c17e2fde3051831a6186b887e"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
- "index 7c8b990..2dfe079 100644",
+ "index 7c8b9908..2dfe0799 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+delete thing.prop"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "71f7d6db03225cbfcc31f2bbd6ab589e9183c55c..629c83e185f6ed3c97976cc604dfb3c5f455c11b"
+ "shas": "c001371459eed13c17e2fde3051831a6186b887e..aeacfbd49b5813111cb6d41d23e1eb0333940a73"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
- "index 2dfe079..9d68dfb 100644",
+ "index 2dfe0799..9d68dfb8 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" delete thing.prop"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "629c83e185f6ed3c97976cc604dfb3c5f455c11b..cf1e4c5bef7af55d4866d7be93a24a523edbbf4f"
+ "shas": "aeacfbd49b5813111cb6d41d23e1eb0333940a73..8f89b423be7695216881a3cf0d40c047dc6b820a"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
- "index 9d68dfb..e69de29 100644",
+ "index 9d68dfb8..e69de29b 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1 +0,0 @@",
"-delete thing.prop"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "cf1e4c5bef7af55d4866d7be93a24a523edbbf4f..56f88d5286e94da2b11b7f6d0a35aa836d4f5921"
+ "shas": "8f89b423be7695216881a3cf0d40c047dc6b820a..f90555ef6eea69038b7aa16bd074797419738b0a"
}]
diff --git a/test/corpus/diff-summaries/javascript/do-while-statement.json b/test/corpus/diff-summaries/javascript/do-while-statement.json
index 49a1461c2..001c74fc9 100644
--- a/test/corpus/diff-summaries/javascript/do-while-statement.json
+++ b/test/corpus/diff-summaries/javascript/do-while-statement.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
- "index e69de29..d1ec804 100644",
+ "index e69de29b..d1ec804b 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",
- "shas": "cd322134775da8db98f5a151ec8e2f5d9eddd3cf..2b58702fac7ff187b0f41a31b6fae16718c0ec4c"
+ "shas": "34742f99e05bf8c6402929d23886b55c725e282e..88a8018f9d3b342ec0120c29471a321f87c39aa2"
}
,{
"testCaseDescription": "javascript-do-while-statement-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
- "index d1ec804..d9a410d 100644",
+ "index d1ec804b..d9a410d6 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" do { console.log(insert); } while (true);"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2b58702fac7ff187b0f41a31b6fae16718c0ec4c..fa2041b0ae98229dc1322fda8ebaa2d98dd4b1f7"
+ "shas": "88a8018f9d3b342ec0120c29471a321f87c39aa2..3879977790b874bb57ec4dc4597ba61abda7cf8d"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-insert-test",
@@ -121,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'replacement' identifier with the 'insert' identifier in the console.log(insert) method call"
+ "summary": "Replaced the 'replacement' identifier with the 'insert' identifier in the console.log(insert) function call"
},
{
"span": {
@@ -159,7 +159,7 @@
],
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
- "index d9a410d..4197835 100644",
+ "index d9a410d6..41978359 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -1,3 +1,3 @@",
@@ -169,7 +169,7 @@
" do { console.log(insert); } while (true);"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "fa2041b0ae98229dc1322fda8ebaa2d98dd4b1f7..c7d0a76295cd609ed29a5c857ff2d885eefb3610"
+ "shas": "3879977790b874bb57ec4dc4597ba61abda7cf8d..df9f4f04301d1eb7046b6fba2afa513beab2da76"
}
,{
"testCaseDescription": "javascript-do-while-statement-replacement-test",
@@ -201,7 +201,7 @@
}
]
},
- "summary": "Replaced the 'insert' identifier with the 'replacement' identifier in the console.log(replacement) method call"
+ "summary": "Replaced the 'insert' identifier with the 'replacement' identifier in the console.log(replacement) function call"
},
{
"span": {
@@ -239,7 +239,7 @@
],
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
- "index 4197835..d9a410d 100644",
+ "index 41978359..d9a410d6 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -1,3 +1,3 @@",
@@ -249,7 +249,7 @@
" do { console.log(insert); } while (true);"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c7d0a76295cd609ed29a5c857ff2d885eefb3610..8887ecec6e5dc8852e1f29ffe74c0b79c304e04e"
+ "shas": "df9f4f04301d1eb7046b6fba2afa513beab2da76..9654bc71a1492e901989b1f1421874a6e352f1eb"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-replacement-test",
@@ -310,7 +310,7 @@
],
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
- "index d9a410d..c5291b4 100644",
+ "index d9a410d6..c5291b47 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -1,3 +1,2 @@",
@@ -320,7 +320,7 @@
"+do { console.log(replacement); } while (false);"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8887ecec6e5dc8852e1f29ffe74c0b79c304e04e..888367feff9a28c449258cd99afd8ac90e069f76"
+ "shas": "9654bc71a1492e901989b1f1421874a6e352f1eb..bcdddc4a78f2fa673c18e3a78d64f1692078e313"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-test",
@@ -351,7 +351,7 @@
],
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
- "index c5291b4..6085cb1 100644",
+ "index c5291b47..6085cb11 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -1,2 +1 @@",
@@ -359,7 +359,7 @@
" do { console.log(replacement); } while (false);"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "888367feff9a28c449258cd99afd8ac90e069f76..622706434ac7e362f28c08d79f7d8302ec086757"
+ "shas": "bcdddc4a78f2fa673c18e3a78d64f1692078e313..60aa16e0f11e94a8ca873354d308e62837210476"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-rest-test",
@@ -390,12 +390,12 @@
],
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
- "index 6085cb1..e69de29 100644",
+ "index 6085cb11..e69de29b 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",
- "shas": "622706434ac7e362f28c08d79f7d8302ec086757..2795ba48a13af4b2c6f240761fd880dc6cd10c2b"
+ "shas": "60aa16e0f11e94a8ca873354d308e62837210476..cfb33c769bbc24766b17e262f1c1eb05b0face8f"
}]
diff --git a/test/corpus/diff-summaries/javascript/export.json b/test/corpus/diff-summaries/javascript/export.json
index 8072fd1fa..9f7fd0db8 100644
--- a/test/corpus/diff-summaries/javascript/export.json
+++ b/test/corpus/diff-summaries/javascript/export.json
@@ -177,7 +177,7 @@
],
"patch": [
"diff --git a/export.js b/export.js",
- "index e69de29..dcd9320 100644",
+ "index e69de29b..dcd9320b 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -0,0 +1,11 @@",
@@ -194,7 +194,7 @@
"+export { import1 as name1, import2 as name2, nameN } from 'bar';"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0eb14098d9cfc48fe7ffb44e37c71cb6cb58c878..5e2e89a442ac0f099046b72d57acaa03dc011ed9"
+ "shas": "b56108ab09b88f198a0ec68e4f7a87ad1b2c06b6..37689b6855efcf22edc9a397b6116b5141ab642b"
}
,{
"testCaseDescription": "javascript-export-replacement-insert-test",
@@ -540,7 +540,7 @@
],
"patch": [
"diff --git a/export.js b/export.js",
- "index dcd9320..c8b53ff 100644",
+ "index dcd9320b..c8b53ff3 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,3 +1,25 @@",
@@ -571,7 +571,7 @@
" export let name1, name2, nameN;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5e2e89a442ac0f099046b72d57acaa03dc011ed9..9e81bf04d8f7a930fb0a612fc5230af600c7c5d2"
+ "shas": "37689b6855efcf22edc9a397b6116b5141ab642b..a587e998ca80b72452fa08e9dc0a82842607673b"
}
,{
"testCaseDescription": "javascript-export-delete-insert-test",
@@ -1304,7 +1304,7 @@
],
"patch": [
"diff --git a/export.js b/export.js",
- "index c8b53ff..ad3f21a 100644",
+ "index c8b53ff3..ad3f21a7 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,14 +1,14 @@",
@@ -1335,7 +1335,7 @@
" export let name1, name2, nameN;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9e81bf04d8f7a930fb0a612fc5230af600c7c5d2..d1bc421a42e531d555179f1135e64e9f19d57095"
+ "shas": "a587e998ca80b72452fa08e9dc0a82842607673b..4032a29478ba2412695dbcc4b7bb948eb09b1f8f"
}
,{
"testCaseDescription": "javascript-export-replacement-test",
@@ -1759,7 +1759,7 @@
],
"patch": [
"diff --git a/export.js b/export.js",
- "index ad3f21a..c8b53ff 100644",
+ "index ad3f21a7..c8b53ff3 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,14 +1,14 @@",
@@ -1790,7 +1790,7 @@
" export let name1, name2, nameN;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d1bc421a42e531d555179f1135e64e9f19d57095..61d845cfdc6aaaba0c4fa01fb8ca41f79556ac37"
+ "shas": "4032a29478ba2412695dbcc4b7bb948eb09b1f8f..4cacea87233cddf0243da69dc293f7c8e6c7a574"
}
,{
"testCaseDescription": "javascript-export-delete-replacement-test",
@@ -2301,7 +2301,7 @@
],
"patch": [
"diff --git a/export.js b/export.js",
- "index c8b53ff..281c672 100644",
+ "index c8b53ff3..281c6726 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,25 +1,3 @@",
@@ -2347,7 +2347,7 @@
"+export { import6 as name6, import7 as name7, nameB } from 'fizz';"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "61d845cfdc6aaaba0c4fa01fb8ca41f79556ac37..06bbce70f8962416f84a41ea00019bfb28b73bf9"
+ "shas": "4cacea87233cddf0243da69dc293f7c8e6c7a574..cdd6691ff292adf83a7de1c4cc4994521b56e9c6"
}
,{
"testCaseDescription": "javascript-export-delete-test",
@@ -2528,7 +2528,7 @@
],
"patch": [
"diff --git a/export.js b/export.js",
- "index 281c672..e105ba7 100644",
+ "index 281c6726..e105ba78 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,14 +1,3 @@",
@@ -2548,7 +2548,7 @@
" export let name3, name4, nameT;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "06bbce70f8962416f84a41ea00019bfb28b73bf9..d1daa5ccf312ddb7b243f8adf15955fac3df1d63"
+ "shas": "cdd6691ff292adf83a7de1c4cc4994521b56e9c6..bc81d61fb61d4658531fb10edde19e87253de887"
}
,{
"testCaseDescription": "javascript-export-delete-rest-test",
@@ -2729,7 +2729,7 @@
],
"patch": [
"diff --git a/export.js b/export.js",
- "index e105ba7..e69de29 100644",
+ "index e105ba78..e69de29b 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,11 +0,0 @@",
@@ -2746,5 +2746,5 @@
"-export { import6 as name6, import7 as name7, nameB } from 'fizz';"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d1daa5ccf312ddb7b243f8adf15955fac3df1d63..925b73e9fde76236d0b037d687edcc925a5cef9a"
+ "shas": "bc81d61fb61d4658531fb10edde19e87253de887..7b8267eabe246347b009d08c9100f36a568a81a6"
}]
diff --git a/test/corpus/diff-summaries/javascript/false.json b/test/corpus/diff-summaries/javascript/false.json
index f64b400e6..87d9ac006 100644
--- a/test/corpus/diff-summaries/javascript/false.json
+++ b/test/corpus/diff-summaries/javascript/false.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/false.js b/false.js",
- "index e69de29..8a63946 100644",
+ "index e69de29b..8a639462 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -0,0 +1 @@",
"+false;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "a56c14e19dec2910d36460e4fca6496da46f6240..6b1a30d6be2d43907c3a1faf581db6c9fe6cc88a"
+ "shas": "d7a5c35ea0a826299a22c96d0b992f92bc85bb91..c0b7401ea04f1b37426f7bc4773e77fdf8c0f3c1"
}
,{
"testCaseDescription": "javascript-false-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/false.js b/false.js",
- "index 8a63946..86574b1 100644",
+ "index 8a639462..86574b16 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" false;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6b1a30d6be2d43907c3a1faf581db6c9fe6cc88a..122e0fae24e99d4f534bb461d9d5fa2900c70e55"
+ "shas": "c0b7401ea04f1b37426f7bc4773e77fdf8c0f3c1..2e31f217aa32ada1925fb2ec1cc0411d0edcd1b0"
}
,{
"testCaseDescription": "javascript-false-delete-insert-test",
@@ -135,7 +135,7 @@
],
"patch": [
"diff --git a/false.js b/false.js",
- "index 86574b1..7bae7c5 100644",
+ "index 86574b16..7bae7c53 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1,3 +1,3 @@",
@@ -145,7 +145,7 @@
" false;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "122e0fae24e99d4f534bb461d9d5fa2900c70e55..6d5ec0ada3f32284c9922934304c708333da7e1f"
+ "shas": "2e31f217aa32ada1925fb2ec1cc0411d0edcd1b0..53d6e0873afb002215a77619b6e3f4604bc27453"
}
,{
"testCaseDescription": "javascript-false-replacement-test",
@@ -191,7 +191,7 @@
],
"patch": [
"diff --git a/false.js b/false.js",
- "index 7bae7c5..86574b1 100644",
+ "index 7bae7c53..86574b16 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1,3 +1,3 @@",
@@ -201,7 +201,7 @@
" false;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6d5ec0ada3f32284c9922934304c708333da7e1f..7291f772ca242bae0a92ab87c1ab6ec2be28d4c1"
+ "shas": "53d6e0873afb002215a77619b6e3f4604bc27453..c2ef01b79b9b22e6e6f49923770ba63b149870a8"
}
,{
"testCaseDescription": "javascript-false-delete-replacement-test",
@@ -262,7 +262,7 @@
],
"patch": [
"diff --git a/false.js b/false.js",
- "index 86574b1..85b5be9 100644",
+ "index 86574b16..85b5be91 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1,3 +1,2 @@",
@@ -272,7 +272,7 @@
"+return false;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7291f772ca242bae0a92ab87c1ab6ec2be28d4c1..018e3b49010dd5359d8071f4a856b6ccef409645"
+ "shas": "c2ef01b79b9b22e6e6f49923770ba63b149870a8..428cba3e1b4d7186ecced8004ddc6b1e82df3f0e"
}
,{
"testCaseDescription": "javascript-false-delete-test",
@@ -303,7 +303,7 @@
],
"patch": [
"diff --git a/false.js b/false.js",
- "index 85b5be9..1f328b3 100644",
+ "index 85b5be91..1f328b3b 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1,2 +1 @@",
@@ -311,7 +311,7 @@
" return false;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "018e3b49010dd5359d8071f4a856b6ccef409645..bda912eec94150ac764d032b1243ec8dba01f3f0"
+ "shas": "428cba3e1b4d7186ecced8004ddc6b1e82df3f0e..6338763787e51da57da095e9e8e91e4d56873327"
}
,{
"testCaseDescription": "javascript-false-delete-rest-test",
@@ -342,12 +342,12 @@
],
"patch": [
"diff --git a/false.js b/false.js",
- "index 1f328b3..e69de29 100644",
+ "index 1f328b3b..e69de29b 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1 +0,0 @@",
"-return false;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "bda912eec94150ac764d032b1243ec8dba01f3f0..f6dfeb42af9db740677fd60341ea39da711f7c81"
+ "shas": "6338763787e51da57da095e9e8e91e4d56873327..d9d6e19c015a3f2dbb9d04d3867b13889dd798ac"
}]
diff --git a/test/corpus/diff-summaries/javascript/for-in-statement.json b/test/corpus/diff-summaries/javascript/for-in-statement.json
index 2151f2b56..1e2157a3b 100644
--- a/test/corpus/diff-summaries/javascript/for-in-statement.json
+++ b/test/corpus/diff-summaries/javascript/for-in-statement.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
- "index e69de29..f928287 100644",
+ "index e69de29b..f9282876 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -0,0 +1 @@",
"+for (thing in things) { thing(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "75f87f22428c68545ebb3f876a1b09caf59d75c9..1d91306ffc69509679ae514ecc2a3403dc94aefb"
+ "shas": "6e93ce14abfffa0befb5a6168efdc830619e0319..4591de1a2b85f3c2813876e233110cc887b0c706"
}
,{
"testCaseDescription": "javascript-for-in-statement-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
- "index f928287..4a482e9 100644",
+ "index f9282876..4a482e9e 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" for (thing in things) { thing(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1d91306ffc69509679ae514ecc2a3403dc94aefb..2f951d1d02db4475f786a87f7077648822ef26d3"
+ "shas": "4591de1a2b85f3c2813876e233110cc887b0c706..c429195ed2092f33ba7e049821ceaec499bf038e"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-insert-test",
@@ -186,7 +186,7 @@
],
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
- "index 4a482e9..e949baf 100644",
+ "index 4a482e9e..e949bafb 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1,3 +1,3 @@",
@@ -196,7 +196,7 @@
" for (thing in things) { thing(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2f951d1d02db4475f786a87f7077648822ef26d3..31f13f455d1c9d9efae42c7695abae57acf4684a"
+ "shas": "c429195ed2092f33ba7e049821ceaec499bf038e..b5d7e5afb889977c0b6a286814a02fd356c15c1e"
}
,{
"testCaseDescription": "javascript-for-in-statement-replacement-test",
@@ -293,7 +293,7 @@
],
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
- "index e949baf..4a482e9 100644",
+ "index e949bafb..4a482e9e 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1,3 +1,3 @@",
@@ -303,7 +303,7 @@
" for (thing in things) { thing(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "31f13f455d1c9d9efae42c7695abae57acf4684a..20bf2c4356e71329f5e131bec7be78669308acc8"
+ "shas": "b5d7e5afb889977c0b6a286814a02fd356c15c1e..b9772b80971e810b2fe559eacc6916548267991e"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-replacement-test",
@@ -364,7 +364,7 @@
],
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
- "index 4a482e9..6b5f12a 100644",
+ "index 4a482e9e..6b5f12ae 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1,3 +1,2 @@",
@@ -374,7 +374,7 @@
"+for (item in items) { item(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "20bf2c4356e71329f5e131bec7be78669308acc8..cc6e8abe393b4d3c5e2b919a60c832b78ad0a4cd"
+ "shas": "b9772b80971e810b2fe559eacc6916548267991e..61a0380174ea230f97ff054f79cd0b004ed3182c"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-test",
@@ -405,7 +405,7 @@
],
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
- "index 6b5f12a..a3d8882 100644",
+ "index 6b5f12ae..a3d8882d 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1,2 +1 @@",
@@ -413,7 +413,7 @@
" for (item in items) { item(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "cc6e8abe393b4d3c5e2b919a60c832b78ad0a4cd..71a7b11ea45ba6cae99bbc5d1bdad0c7eb526a3b"
+ "shas": "61a0380174ea230f97ff054f79cd0b004ed3182c..f0e33cad1a66b2bebde032276a7728a3e8b754ea"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-rest-test",
@@ -444,12 +444,12 @@
],
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
- "index a3d8882..e69de29 100644",
+ "index a3d8882d..e69de29b 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1 +0,0 @@",
"-for (item in items) { item(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "71a7b11ea45ba6cae99bbc5d1bdad0c7eb526a3b..d1b2bee18a7da4fefa2a4786b2f692fc5795f48c"
+ "shas": "f0e33cad1a66b2bebde032276a7728a3e8b754ea..03a1b4a15f149e9715aa37bf2334cb4f05f0e8ff"
}]
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 bca171c0b..7b90b0181 100644
--- a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json
+++ b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
- "index e69de29..c467478 100644",
+ "index e69de29b..c467478a 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",
- "shas": "1c2dbb18fb6fc930b3d0e6bb31a559a853be5c63..974a2623d96129b8a5eb74659c0040931fe6597a"
+ "shas": "a7b8d1dcde9a2945edc002250d8df6d841189c39..365faf7882dbb2f146184940d80d82a70e647ea4"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
- "index c467478..0147d31 100644",
+ "index c467478a..0147d318 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" for (key in something && i = 0; i < n; i++) { doSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "974a2623d96129b8a5eb74659c0040931fe6597a..37f9b64351b20f87cdd2d65e794e8b43ea684959"
+ "shas": "365faf7882dbb2f146184940d80d82a70e647ea4..75a82c7096f5dade494e047719babc2f48789eaa"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test",
@@ -159,7 +159,7 @@
],
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
- "index 0147d31..306fa88 100644",
+ "index 0147d318..306fa88a 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -1,3 +1,3 @@",
@@ -169,7 +169,7 @@
" for (key in something && i = 0; i < n; i++) { doSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "37f9b64351b20f87cdd2d65e794e8b43ea684959..639c4e9d99aa30a48f0403a42eaf81f85a194e22"
+ "shas": "75a82c7096f5dade494e047719babc2f48789eaa..5bdcc57491e4a99dd0b0e2c4c1f70e5ee0289e69"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test",
@@ -239,7 +239,7 @@
],
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
- "index 306fa88..0147d31 100644",
+ "index 306fa88a..0147d318 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -1,3 +1,3 @@",
@@ -249,7 +249,7 @@
" for (key in something && i = 0; i < n; i++) { doSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "639c4e9d99aa30a48f0403a42eaf81f85a194e22..8d475ef797fcd08a47c73f033c305642c4279115"
+ "shas": "5bdcc57491e4a99dd0b0e2c4c1f70e5ee0289e69..47d0ed7147dfb8cc9825138278e7bfaac9bc4186"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test",
@@ -310,7 +310,7 @@
],
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
- "index 0147d31..f23fa31 100644",
+ "index 0147d318..f23fa316 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -1,3 +1,2 @@",
@@ -320,7 +320,7 @@
"+for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8d475ef797fcd08a47c73f033c305642c4279115..d2051aee8f163a567cf3a5ff4060579795e0a2a1"
+ "shas": "47d0ed7147dfb8cc9825138278e7bfaac9bc4186..3d5f95b6f38777fa1f8b80599af5f5b39651570e"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-test",
@@ -351,7 +351,7 @@
],
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
- "index f23fa31..e968160 100644",
+ "index f23fa316..e9681607 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -1,2 +1 @@",
@@ -359,7 +359,7 @@
" for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d2051aee8f163a567cf3a5ff4060579795e0a2a1..068a5eccf07c8be3b3a95d6eceadf7062d7b942d"
+ "shas": "3d5f95b6f38777fa1f8b80599af5f5b39651570e..76d098119efc28256e6574fd24adcb007ddba5f1"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test",
@@ -390,12 +390,12 @@
],
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
- "index e968160..e69de29 100644",
+ "index e9681607..e69de29b 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",
- "shas": "068a5eccf07c8be3b3a95d6eceadf7062d7b942d..9c2fa1f20200ecb26074ec348c75c13c22138f87"
+ "shas": "76d098119efc28256e6574fd24adcb007ddba5f1..2b21000901a57001f039986154173f06d53be8a6"
}]
diff --git a/test/corpus/diff-summaries/javascript/for-of-statement.json b/test/corpus/diff-summaries/javascript/for-of-statement.json
index aca0dea49..84478bfda 100644
--- a/test/corpus/diff-summaries/javascript/for-of-statement.json
+++ b/test/corpus/diff-summaries/javascript/for-of-statement.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
- "index e69de29..1ed2754 100644",
+ "index e69de29b..1ed27542 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",
- "shas": "9c2fa1f20200ecb26074ec348c75c13c22138f87..c46e44d842f77789f61d1f25221f0449f2d580c5"
+ "shas": "2b21000901a57001f039986154173f06d53be8a6..c2eb1bd5f31917fe68bdd408c3594c69b36834e6"
}
,{
"testCaseDescription": "javascript-for-of-statement-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
- "index 1ed2754..ab20ded 100644",
+ "index 1ed27542..ab20ded2 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" for (let item of items) { process(item); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c46e44d842f77789f61d1f25221f0449f2d580c5..1c06836a9dafef9518b54b9409dc10e9e4402666"
+ "shas": "c2eb1bd5f31917fe68bdd408c3594c69b36834e6..dd1aaacc8c2dc9ba44164e9c19594594b54772e9"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-insert-test",
@@ -186,7 +186,7 @@
],
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
- "index ab20ded..19561a3 100644",
+ "index ab20ded2..19561a3e 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -1,3 +1,3 @@",
@@ -196,7 +196,7 @@
" for (let item of items) { process(item); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1c06836a9dafef9518b54b9409dc10e9e4402666..4c79ce75c12d7e2b77bd33d6f7e4f1d839ee88a8"
+ "shas": "dd1aaacc8c2dc9ba44164e9c19594594b54772e9..9d17d54ae7597e671bbe2bbbca1647205ce65dce"
}
,{
"testCaseDescription": "javascript-for-of-statement-replacement-test",
@@ -293,7 +293,7 @@
],
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
- "index 19561a3..ab20ded 100644",
+ "index 19561a3e..ab20ded2 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -1,3 +1,3 @@",
@@ -303,7 +303,7 @@
" for (let item of items) { process(item); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4c79ce75c12d7e2b77bd33d6f7e4f1d839ee88a8..cd97645bfe60051a1bbd7a490394b00b6df48a7d"
+ "shas": "9d17d54ae7597e671bbe2bbbca1647205ce65dce..dae7f960db312022d23ff082aba5a78642a561cd"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-replacement-test",
@@ -364,7 +364,7 @@
],
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
- "index ab20ded..62db34f 100644",
+ "index ab20ded2..62db34f8 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -1,3 +1,2 @@",
@@ -374,7 +374,7 @@
"+for (let thing of things) { process(thing); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "cd97645bfe60051a1bbd7a490394b00b6df48a7d..3fd962ae8d2bc510b50e7e85ef1ce4ad04375eb8"
+ "shas": "dae7f960db312022d23ff082aba5a78642a561cd..811a60e87ba626685fe89f707187e02c304fac32"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-test",
@@ -405,7 +405,7 @@
],
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
- "index 62db34f..5170ce4 100644",
+ "index 62db34f8..5170ce4b 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -1,2 +1 @@",
@@ -413,7 +413,7 @@
" for (let thing of things) { process(thing); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3fd962ae8d2bc510b50e7e85ef1ce4ad04375eb8..821a3c7b8a7b00f8a8ad7967aed163a12f042d10"
+ "shas": "811a60e87ba626685fe89f707187e02c304fac32..6189b7baec6feb5f7bc08b781076f3acd9a0d50e"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-rest-test",
@@ -444,12 +444,12 @@
],
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
- "index 5170ce4..e69de29 100644",
+ "index 5170ce4b..e69de29b 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",
- "shas": "821a3c7b8a7b00f8a8ad7967aed163a12f042d10..0b1a50d075cdb5202c523f929502c24a9fce63ce"
+ "shas": "6189b7baec6feb5f7bc08b781076f3acd9a0d50e..0494efa588d0a283d42c62a35bcee1f439b6a16d"
}]
diff --git a/test/corpus/diff-summaries/javascript/for-statement.json b/test/corpus/diff-summaries/javascript/for-statement.json
index b5610becd..39f46dc4c 100644
--- a/test/corpus/diff-summaries/javascript/for-statement.json
+++ b/test/corpus/diff-summaries/javascript/for-statement.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
- "index e69de29..2f51258 100644",
+ "index e69de29b..2f51258e 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",
- "shas": "eaeb10729b105d290f4091fea5f04c34030bb5a5..40bfcf71debc3d20926578f5d788f319165ccdbb"
+ "shas": "e2f5e2a31d37bfe30697e216363db3575aa06a6a..9a3f882a6921d8a2807d088e694edc3f6d4fefa1"
}
,{
"testCaseDescription": "javascript-for-statement-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
- "index 2f51258..095241f 100644",
+ "index 2f51258e..095241f1 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" for (i = 0, init(); i < 10; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "40bfcf71debc3d20926578f5d788f319165ccdbb..14acd05cf2f47feba3234c70af8afe86828370ce"
+ "shas": "9a3f882a6921d8a2807d088e694edc3f6d4fefa1..e3ea2d4f24e771b6c9820d2356a99e7237d96b49"
}
,{
"testCaseDescription": "javascript-for-statement-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
- "index 095241f..9b0e26d 100644",
+ "index 095241f1..9b0e26d4 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" for (i = 0, init(); i < 10; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "14acd05cf2f47feba3234c70af8afe86828370ce..26784319f5f567d3017095b6f9d0ca081043b817"
+ "shas": "e3ea2d4f24e771b6c9820d2356a99e7237d96b49..1f9261f5d8dc568a6c17844d43872e03f64e641d"
}
,{
"testCaseDescription": "javascript-for-statement-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
- "index 9b0e26d..095241f 100644",
+ "index 9b0e26d4..095241f1 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" for (i = 0, init(); i < 10; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "26784319f5f567d3017095b6f9d0ca081043b817..5b15f8e9f8b68a8e4f4ba6ec6642a3cb37db7c60"
+ "shas": "1f9261f5d8dc568a6c17844d43872e03f64e641d..e585ba38f3f0aa601f846c34a898217167081202"
}
,{
"testCaseDescription": "javascript-for-statement-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
- "index 095241f..39af699 100644",
+ "index 095241f1..39af699a 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+for (i = 0, init(); i < 100; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5b15f8e9f8b68a8e4f4ba6ec6642a3cb37db7c60..70806220f9fba3804c162aed68cdfcb25c39ff0a"
+ "shas": "e585ba38f3f0aa601f846c34a898217167081202..8e99fa24d58ed9413ef72b84fc5d6a536de55ba2"
}
,{
"testCaseDescription": "javascript-for-statement-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
- "index 39af699..de8ae87 100644",
+ "index 39af699a..de8ae87b 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" for (i = 0, init(); i < 100; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "70806220f9fba3804c162aed68cdfcb25c39ff0a..9d01a0008d001fc966736db7d1583e0415da98fd"
+ "shas": "8e99fa24d58ed9413ef72b84fc5d6a536de55ba2..d7f1b547f69ddd450adce8a2d22d27f8b64db5dc"
}
,{
"testCaseDescription": "javascript-for-statement-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
- "index de8ae87..e69de29 100644",
+ "index de8ae87b..e69de29b 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",
- "shas": "9d01a0008d001fc966736db7d1583e0415da98fd..10c888c0caabf36cb211a96640afbe435dfad3fb"
+ "shas": "d7f1b547f69ddd450adce8a2d22d27f8b64db5dc..b8e96cb516ef4cd80a86e0b6a00f5d4e542141dd"
}]
diff --git a/test/corpus/diff-summaries/javascript/function-call-args.json b/test/corpus/diff-summaries/javascript/function-call-args.json
index b73044ee5..1ee6701bf 100644
--- a/test/corpus/diff-summaries/javascript/function-call-args.json
+++ b/test/corpus/diff-summaries/javascript/function-call-args.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/function-call-args.js b/function-call-args.js",
- "index e69de29..699333d 100644",
+ "index e69de29b..699333de 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",
- "shas": "5d5d40b2fa515dfcb7494d9b83f22687c56de0f5..d2a8bcf4eb5c5193cb358f09a81b0239be2a84ad"
+ "shas": "ff5044f4617b79b896e8da9c860b589d4022aa5b..134a719c5ccc94c9a8583a521e8d4b4666ede5b1"
}
,{
"testCaseDescription": "javascript-function-call-args-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/function-call-args.js b/function-call-args.js",
- "index 699333d..3f4ee6e 100644",
+ "index 699333de..3f4ee6ef 100644",
"--- a/function-call-args.js",
"+++ b/function-call-args.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d2a8bcf4eb5c5193cb358f09a81b0239be2a84ad..539cee544c8600977bd76181a692ef4e27c4b759"
+ "shas": "134a719c5ccc94c9a8583a521e8d4b4666ede5b1..3ec69cfc69155ac3e026b36ac8a41d575b4dc044"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-insert-test",
@@ -202,7 +202,7 @@
}
]
},
- "summary": "Replaced the 'b' identifier with the 'a' identifier in the console.log(a) method call"
+ "summary": "Replaced the 'b' identifier with the 'a' identifier in the console.log(a) function call"
},
{
"span": {
@@ -267,7 +267,7 @@
],
"patch": [
"diff --git a/function-call-args.js b/function-call-args.js",
- "index 3f4ee6e..dc419cb 100644",
+ "index 3f4ee6ef..dc419cba 100644",
"--- a/function-call-args.js",
"+++ b/function-call-args.js",
"@@ -1,3 +1,3 @@",
@@ -277,7 +277,7 @@
" someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "539cee544c8600977bd76181a692ef4e27c4b759..f808e14f78dbe08885649be38dff25564f90fd98"
+ "shas": "3ec69cfc69155ac3e026b36ac8a41d575b4dc044..892d8ea0f7fe8285bae3236b781249c94c60ec84"
}
,{
"testCaseDescription": "javascript-function-call-args-replacement-test",
@@ -390,7 +390,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'b' identifier in the console.log(b) method call"
+ "summary": "Replaced the 'a' identifier with the 'b' identifier in the console.log(b) function call"
},
{
"span": {
@@ -455,7 +455,7 @@
],
"patch": [
"diff --git a/function-call-args.js b/function-call-args.js",
- "index dc419cb..3f4ee6e 100644",
+ "index dc419cba..3f4ee6ef 100644",
"--- a/function-call-args.js",
"+++ b/function-call-args.js",
"@@ -1,3 +1,3 @@",
@@ -465,7 +465,7 @@
" someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f808e14f78dbe08885649be38dff25564f90fd98..6df8cc03d89ad9408f10b3e84a8168891e16c824"
+ "shas": "892d8ea0f7fe8285bae3236b781249c94c60ec84..09414b2a48c0168304c23b6878394c51ce959392"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-replacement-test",
@@ -526,7 +526,7 @@
],
"patch": [
"diff --git a/function-call-args.js b/function-call-args.js",
- "index 3f4ee6e..cae967b 100644",
+ "index 3f4ee6ef..cae967b6 100644",
"--- a/function-call-args.js",
"+++ b/function-call-args.js",
"@@ -1,3 +1,2 @@",
@@ -536,7 +536,7 @@
"+someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6df8cc03d89ad9408f10b3e84a8168891e16c824..8fe5a2260c0258b29e266f904dcdb1dbe02d4c10"
+ "shas": "09414b2a48c0168304c23b6878394c51ce959392..0020b036b7829f6ca7ba7f32e211439f74b73d63"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-test",
@@ -567,7 +567,7 @@
],
"patch": [
"diff --git a/function-call-args.js b/function-call-args.js",
- "index cae967b..0d19573 100644",
+ "index cae967b6..0d19573d 100644",
"--- a/function-call-args.js",
"+++ b/function-call-args.js",
"@@ -1,2 +1 @@",
@@ -575,7 +575,7 @@
" someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8fe5a2260c0258b29e266f904dcdb1dbe02d4c10..657ddea03b3413ea6f2d4e8546403ec115769828"
+ "shas": "0020b036b7829f6ca7ba7f32e211439f74b73d63..550eba6d0f7ad10f05f0fbcf145ad4c69fb98579"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-rest-test",
@@ -606,12 +606,12 @@
],
"patch": [
"diff --git a/function-call-args.js b/function-call-args.js",
- "index 0d19573..e69de29 100644",
+ "index 0d19573d..e69de29b 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",
- "shas": "657ddea03b3413ea6f2d4e8546403ec115769828..b1ed87edc6bf561edc524058ab781a95970a3258"
+ "shas": "550eba6d0f7ad10f05f0fbcf145ad4c69fb98579..bc8f6203c7c5033d706c0155313d250aff41b6ce"
}]
diff --git a/test/corpus/diff-summaries/javascript/function-call.json b/test/corpus/diff-summaries/javascript/function-call.json
index f61405e32..95ad0e151 100644
--- a/test/corpus/diff-summaries/javascript/function-call.json
+++ b/test/corpus/diff-summaries/javascript/function-call.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/function-call.js b/function-call.js",
- "index e69de29..8bd95e0 100644",
+ "index e69de29b..8bd95e09 100644",
"--- a/function-call.js",
"+++ b/function-call.js",
"@@ -0,0 +1 @@",
"+someFunction(arg1, \"arg2\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5ef42771e35b5af39f3befe137fedf40f174a5c7..00b36bff0934786a0071eff76e45c17c464e432a"
+ "shas": "65ec4b91fc50d92244f898493564425dc91dec99..b615308df966b578cf01e5d48566843aa41cdb9a"
}
,{
"testCaseDescription": "javascript-function-call-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/function-call.js b/function-call.js",
- "index 8bd95e0..6bb4cf3 100644",
+ "index 8bd95e09..6bb4cf3f 100644",
"--- a/function-call.js",
"+++ b/function-call.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" someFunction(arg1, \"arg2\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "00b36bff0934786a0071eff76e45c17c464e432a..520cba16d2faea8fd35a81086ea0a0b2405bf082"
+ "shas": "b615308df966b578cf01e5d48566843aa41cdb9a..bbeb6c549afd5768be327d11d6f0586b19b54f5f"
}
,{
"testCaseDescription": "javascript-function-call-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/function-call.js b/function-call.js",
- "index 6bb4cf3..b38c232 100644",
+ "index 6bb4cf3f..b38c232b 100644",
"--- a/function-call.js",
"+++ b/function-call.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" someFunction(arg1, \"arg2\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "520cba16d2faea8fd35a81086ea0a0b2405bf082..8f84b861874020df6e144f16bbccb5221b1543e4"
+ "shas": "bbeb6c549afd5768be327d11d6f0586b19b54f5f..34be18f8448763874f7ef124b682bfd0cf7f5d6c"
}
,{
"testCaseDescription": "javascript-function-call-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/function-call.js b/function-call.js",
- "index b38c232..6bb4cf3 100644",
+ "index b38c232b..6bb4cf3f 100644",
"--- a/function-call.js",
"+++ b/function-call.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" someFunction(arg1, \"arg2\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8f84b861874020df6e144f16bbccb5221b1543e4..718e8939aaef9685a140e371b050e8933450a215"
+ "shas": "34be18f8448763874f7ef124b682bfd0cf7f5d6c..48a4faebbb542de45e082a48f7ebc7dc146434ee"
}
,{
"testCaseDescription": "javascript-function-call-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/function-call.js b/function-call.js",
- "index 6bb4cf3..3e15c6a 100644",
+ "index 6bb4cf3f..3e15c6ac 100644",
"--- a/function-call.js",
"+++ b/function-call.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+someFunction(arg1, \"arg3\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "718e8939aaef9685a140e371b050e8933450a215..35112398ed93567a624e79597194400f3a6ba5ed"
+ "shas": "48a4faebbb542de45e082a48f7ebc7dc146434ee..830303cbd8c1c18ab526b72ee0af22ce1117f291"
}
,{
"testCaseDescription": "javascript-function-call-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/function-call.js b/function-call.js",
- "index 3e15c6a..1add64b 100644",
+ "index 3e15c6ac..1add64b5 100644",
"--- a/function-call.js",
"+++ b/function-call.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" someFunction(arg1, \"arg3\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "35112398ed93567a624e79597194400f3a6ba5ed..2928901cff45e08e275b3c7cc5559704326f2974"
+ "shas": "830303cbd8c1c18ab526b72ee0af22ce1117f291..907c562a9a25a3d6b2cba73e693b57825dc8157f"
}
,{
"testCaseDescription": "javascript-function-call-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/function-call.js b/function-call.js",
- "index 1add64b..e69de29 100644",
+ "index 1add64b5..e69de29b 100644",
"--- a/function-call.js",
"+++ b/function-call.js",
"@@ -1 +0,0 @@",
"-someFunction(arg1, \"arg3\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2928901cff45e08e275b3c7cc5559704326f2974..f8662860eb083b9e95b5cc1c706a7872a4779532"
+ "shas": "907c562a9a25a3d6b2cba73e693b57825dc8157f..bded2c0215b6dc80127e031b7d9978f1883709b1"
}]
diff --git a/test/corpus/diff-summaries/javascript/function.json b/test/corpus/diff-summaries/javascript/function.json
index f3e71eab3..80d9f69e5 100644
--- a/test/corpus/diff-summaries/javascript/function.json
+++ b/test/corpus/diff-summaries/javascript/function.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/function.js b/function.js",
- "index e69de29..2d8d739 100644",
+ "index e69de29b..2d8d739d 100644",
"--- a/function.js",
"+++ b/function.js",
"@@ -0,0 +1 @@",
"+function(arg1, arg2) { arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0bdf412036a9a6aea51108a20404c37541fffcfb..c76e13ba716fc18e9924e1f4675845f61823c9c7"
+ "shas": "6a98861e426cf72452392e143d875b8ccd968a2c..a9d3342f1523a3bdfb2089737e26c073d72518e1"
}
,{
"testCaseDescription": "javascript-function-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/function.js b/function.js",
- "index 2d8d739..4389406 100644",
+ "index 2d8d739d..43894067 100644",
"--- a/function.js",
"+++ b/function.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" function(arg1, arg2) { arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c76e13ba716fc18e9924e1f4675845f61823c9c7..7c1485f22ad0c4bc98a22cdb8d341d2eb97fcab8"
+ "shas": "a9d3342f1523a3bdfb2089737e26c073d72518e1..ed5a8373997dc1879db9c1c9168d3b26e7b3dc90"
}
,{
"testCaseDescription": "javascript-function-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/function.js b/function.js",
- "index 4389406..924c99e 100644",
+ "index 43894067..924c99e8 100644",
"--- a/function.js",
"+++ b/function.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" function(arg1, arg2) { arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7c1485f22ad0c4bc98a22cdb8d341d2eb97fcab8..9e13719e7c1614958c3528e609d7ac1cfb068fe6"
+ "shas": "ed5a8373997dc1879db9c1c9168d3b26e7b3dc90..dc33c0452310a395ba61cd50472fcbb7c09eb19a"
}
,{
"testCaseDescription": "javascript-function-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/function.js b/function.js",
- "index 924c99e..4389406 100644",
+ "index 924c99e8..43894067 100644",
"--- a/function.js",
"+++ b/function.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" function(arg1, arg2) { arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9e13719e7c1614958c3528e609d7ac1cfb068fe6..e36301a0b4cc27e38d4c77c49f97e1a6ba816fbb"
+ "shas": "dc33c0452310a395ba61cd50472fcbb7c09eb19a..a95c62fef6c7f158ccb26b14adceb5a3a3f52ad1"
}
,{
"testCaseDescription": "javascript-function-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/function.js b/function.js",
- "index 4389406..254dbcf 100644",
+ "index 43894067..254dbcf8 100644",
"--- a/function.js",
"+++ b/function.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+function(arg1, arg2) { arg1; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "e36301a0b4cc27e38d4c77c49f97e1a6ba816fbb..fbc7371a528f691d2e0b43ceed413fab19186b82"
+ "shas": "a95c62fef6c7f158ccb26b14adceb5a3a3f52ad1..74d7b44b4bf8045b15dbd99ff56365d56beca8c3"
}
,{
"testCaseDescription": "javascript-function-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/function.js b/function.js",
- "index 254dbcf..b37e867 100644",
+ "index 254dbcf8..b37e8671 100644",
"--- a/function.js",
"+++ b/function.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" function(arg1, arg2) { arg1; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "fbc7371a528f691d2e0b43ceed413fab19186b82..dd37f0a24f8a677191eb11c1dad4119d46e35d14"
+ "shas": "74d7b44b4bf8045b15dbd99ff56365d56beca8c3..4a809529033c4b4ce9ac0dff95e378035c98a29f"
}
,{
"testCaseDescription": "javascript-function-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/function.js b/function.js",
- "index b37e867..e69de29 100644",
+ "index b37e8671..e69de29b 100644",
"--- a/function.js",
"+++ b/function.js",
"@@ -1 +0,0 @@",
"-function(arg1, arg2) { arg1; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "dd37f0a24f8a677191eb11c1dad4119d46e35d14..d700dc51fee7a3dd557906dcdf46d426285d7955"
+ "shas": "4a809529033c4b4ce9ac0dff95e378035c98a29f..9adc811773ddcc66050c739b5bc900c4c2daff55"
}]
diff --git a/test/corpus/diff-summaries/javascript/generator-function.json b/test/corpus/diff-summaries/javascript/generator-function.json
index 7a96187dd..c56f897a7 100644
--- a/test/corpus/diff-summaries/javascript/generator-function.json
+++ b/test/corpus/diff-summaries/javascript/generator-function.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/generator-function.js b/generator-function.js",
- "index e69de29..04e8a59 100644",
+ "index e69de29b..04e8a59b 100644",
"--- a/generator-function.js",
"+++ b/generator-function.js",
"@@ -0,0 +1 @@",
"+function *generateStuff(arg1, arg2) { yield; yield arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5cab8720cde055f6d78f5c5deaf8980b89a434e1..8ff6dd40a182ab5500d976f04b8d0e919d045ddc"
+ "shas": "a50f5d25657afa02329debd2a87b7ffbb8f2b76d..9df04cfb26b2766e7e78bcd47ee06b6becb2f572"
}
,{
"testCaseDescription": "javascript-generator-function-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/generator-function.js b/generator-function.js",
- "index 04e8a59..ed5c037 100644",
+ "index 04e8a59b..ed5c0370 100644",
"--- a/generator-function.js",
"+++ b/generator-function.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" function *generateStuff(arg1, arg2) { yield; yield arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8ff6dd40a182ab5500d976f04b8d0e919d045ddc..e3273bce016747d95cbc043e14d23cda41b65129"
+ "shas": "9df04cfb26b2766e7e78bcd47ee06b6becb2f572..ec757a8900be08223339e8e9727898b3255d8f08"
}
,{
"testCaseDescription": "javascript-generator-function-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/generator-function.js b/generator-function.js",
- "index ed5c037..0895c3f 100644",
+ "index ed5c0370..0895c3fd 100644",
"--- a/generator-function.js",
"+++ b/generator-function.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" function *generateStuff(arg1, arg2) { yield; yield arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "e3273bce016747d95cbc043e14d23cda41b65129..3dd2a62eface3915c946a63ecef0c9134bf5b9be"
+ "shas": "ec757a8900be08223339e8e9727898b3255d8f08..15ec5e1fa46bd4e16d253840d6f0102c44496fed"
}
,{
"testCaseDescription": "javascript-generator-function-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/generator-function.js b/generator-function.js",
- "index 0895c3f..ed5c037 100644",
+ "index 0895c3fd..ed5c0370 100644",
"--- a/generator-function.js",
"+++ b/generator-function.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" function *generateStuff(arg1, arg2) { yield; yield arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3dd2a62eface3915c946a63ecef0c9134bf5b9be..9a4d77ff9359a6c8fe9ab42d88157282b742e1be"
+ "shas": "15ec5e1fa46bd4e16d253840d6f0102c44496fed..b7e7155e6794ba2a257dcbc55a91f8b12093fa58"
}
,{
"testCaseDescription": "javascript-generator-function-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/generator-function.js b/generator-function.js",
- "index ed5c037..1dae105 100644",
+ "index ed5c0370..1dae1059 100644",
"--- a/generator-function.js",
"+++ b/generator-function.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+function *generateNewStuff(arg1, arg2) { yield; yield arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9a4d77ff9359a6c8fe9ab42d88157282b742e1be..63a8b6f6c41bdd248590069ba8f59d53a3b0992f"
+ "shas": "b7e7155e6794ba2a257dcbc55a91f8b12093fa58..f5c134c2262cb4b15c43b2c35a34ae3812d4cfd8"
}
,{
"testCaseDescription": "javascript-generator-function-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/generator-function.js b/generator-function.js",
- "index 1dae105..5846d1c 100644",
+ "index 1dae1059..5846d1c0 100644",
"--- a/generator-function.js",
"+++ b/generator-function.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" function *generateNewStuff(arg1, arg2) { yield; yield arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "63a8b6f6c41bdd248590069ba8f59d53a3b0992f..2087f684c9ba7fa39876477f2eacf8b9b12949fa"
+ "shas": "f5c134c2262cb4b15c43b2c35a34ae3812d4cfd8..51e5241d63f1a14e77194ba7b954d06d11de1600"
}
,{
"testCaseDescription": "javascript-generator-function-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/generator-function.js b/generator-function.js",
- "index 5846d1c..e69de29 100644",
+ "index 5846d1c0..e69de29b 100644",
"--- a/generator-function.js",
"+++ b/generator-function.js",
"@@ -1 +0,0 @@",
"-function *generateNewStuff(arg1, arg2) { yield; yield arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2087f684c9ba7fa39876477f2eacf8b9b12949fa..973cce7b94116a9e6e8b399f9f0a50bd107fb9b5"
+ "shas": "51e5241d63f1a14e77194ba7b954d06d11de1600..35363e93d3151d395860548f66a39be33fcc6b34"
}]
diff --git a/test/corpus/diff-summaries/javascript/identifier.json b/test/corpus/diff-summaries/javascript/identifier.json
index 96570ae7d..63af2fffe 100644
--- a/test/corpus/diff-summaries/javascript/identifier.json
+++ b/test/corpus/diff-summaries/javascript/identifier.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/identifier.js b/identifier.js",
- "index e69de29..1cf4ad0 100644",
+ "index e69de29b..1cf4ad05 100644",
"--- a/identifier.js",
"+++ b/identifier.js",
"@@ -0,0 +1 @@",
"+theVar;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2642fef686808ac2a6c5edde323e87257f4f2983..369e63ae9927770fe9ca2fd662ca648e43ab72e5"
+ "shas": "23f245e71b4513803366aff2b4ae93549ad9d3fa..cdaacae44dc6aa4a3aba0e68c2459f5065fd1fa4"
}
,{
"testCaseDescription": "javascript-identifier-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/identifier.js b/identifier.js",
- "index 1cf4ad0..888855a 100644",
+ "index 1cf4ad05..888855ad 100644",
"--- a/identifier.js",
"+++ b/identifier.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" theVar;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "369e63ae9927770fe9ca2fd662ca648e43ab72e5..ee416c16400890b8f6351b1c8113657cb7671eb7"
+ "shas": "cdaacae44dc6aa4a3aba0e68c2459f5065fd1fa4..1389abc96bdc1a98d47c21fd7d6740d4eeca4269"
}
,{
"testCaseDescription": "javascript-identifier-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/identifier.js b/identifier.js",
- "index 888855a..60e041c 100644",
+ "index 888855ad..60e041c1 100644",
"--- a/identifier.js",
"+++ b/identifier.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" theVar;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ee416c16400890b8f6351b1c8113657cb7671eb7..13d808ca205317e4c1b13c036517ed17cdde1da3"
+ "shas": "1389abc96bdc1a98d47c21fd7d6740d4eeca4269..3c9356ded5de6099c8d07a2edba09dfbbeb5807c"
}
,{
"testCaseDescription": "javascript-identifier-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/identifier.js b/identifier.js",
- "index 60e041c..888855a 100644",
+ "index 60e041c1..888855ad 100644",
"--- a/identifier.js",
"+++ b/identifier.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" theVar;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "13d808ca205317e4c1b13c036517ed17cdde1da3..1f1988b798d7bd2558d1d050b242ef4afbd52629"
+ "shas": "3c9356ded5de6099c8d07a2edba09dfbbeb5807c..cfaa88230fcf2d750b14d9e07f3fd13a9d254b36"
}
,{
"testCaseDescription": "javascript-identifier-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/identifier.js b/identifier.js",
- "index 888855a..fbc7b28 100644",
+ "index 888855ad..fbc7b28e 100644",
"--- a/identifier.js",
"+++ b/identifier.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+theVar2"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1f1988b798d7bd2558d1d050b242ef4afbd52629..6408b95d2773e060ccc2c624b319447b326c8a51"
+ "shas": "cfaa88230fcf2d750b14d9e07f3fd13a9d254b36..282c008a1c6565c04e67798c059f42f44495243f"
}
,{
"testCaseDescription": "javascript-identifier-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/identifier.js b/identifier.js",
- "index fbc7b28..7276d95 100644",
+ "index fbc7b28e..7276d95d 100644",
"--- a/identifier.js",
"+++ b/identifier.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" theVar2"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6408b95d2773e060ccc2c624b319447b326c8a51..011d19e2d6ea45758e3df50809069437b44911b5"
+ "shas": "282c008a1c6565c04e67798c059f42f44495243f..44cb18591cf8d85ba07812c409c991217cd383ba"
}
,{
"testCaseDescription": "javascript-identifier-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/identifier.js b/identifier.js",
- "index 7276d95..e69de29 100644",
+ "index 7276d95d..e69de29b 100644",
"--- a/identifier.js",
"+++ b/identifier.js",
"@@ -1 +0,0 @@",
"-theVar2"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "011d19e2d6ea45758e3df50809069437b44911b5..5180fa74c7ae39b3c2cb94b9b5498307af385e5c"
+ "shas": "44cb18591cf8d85ba07812c409c991217cd383ba..62c20bfb9474af540a2ab5d5be1a93530bd21eb8"
}]
diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json
index 2471cd96f..884101abb 100644
--- a/test/corpus/diff-summaries/javascript/if-else.json
+++ b/test/corpus/diff-summaries/javascript/if-else.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/if-else.js b/if-else.js",
- "index e69de29..d81ebad 100644",
+ "index e69de29b..d81ebadd 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",
- "shas": "ee538d5b471190fe27f80e1defc319f36f5f9c38..d5f532daeb84c4dd664519d388575b8891e7e25a"
+ "shas": "9b27e4158f8b990b3f7ca2f77fcf65bf40e26802..6da4e4af4550225b9f9493faa2575360b93f8e5f"
}
,{
"testCaseDescription": "javascript-if-else-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/if-else.js b/if-else.js",
- "index d81ebad..6bb0eaa 100644",
+ "index d81ebadd..6bb0eaa7 100644",
"--- a/if-else.js",
"+++ b/if-else.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" if (x) y; else if (a) b; else if (c) d; else if (e) f; else g"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d5f532daeb84c4dd664519d388575b8891e7e25a..539d5f1eb9ec34131ed8d31c596c38285f83e6bf"
+ "shas": "6da4e4af4550225b9f9493faa2575360b93f8e5f..8a8df26cb938506ec102e908d4552929a7073d00"
}
,{
"testCaseDescription": "javascript-if-else-delete-insert-test",
@@ -354,7 +354,7 @@
],
"patch": [
"diff --git a/if-else.js b/if-else.js",
- "index 6bb0eaa..2034be1 100644",
+ "index 6bb0eaa7..2034be1b 100644",
"--- a/if-else.js",
"+++ b/if-else.js",
"@@ -1,3 +1,3 @@",
@@ -364,7 +364,7 @@
" if (x) y; else if (a) b; else if (c) d; else if (e) f; else g"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "539d5f1eb9ec34131ed8d31c596c38285f83e6bf..f525e3671aa6d43caf17c2582f3c746f07570b7a"
+ "shas": "8a8df26cb938506ec102e908d4552929a7073d00..0dc2b9999e933cc5f579be3de82aafbe951cd42c"
}
,{
"testCaseDescription": "javascript-if-else-replacement-test",
@@ -629,7 +629,7 @@
],
"patch": [
"diff --git a/if-else.js b/if-else.js",
- "index 2034be1..6bb0eaa 100644",
+ "index 2034be1b..6bb0eaa7 100644",
"--- a/if-else.js",
"+++ b/if-else.js",
"@@ -1,3 +1,3 @@",
@@ -639,7 +639,7 @@
" if (x) y; else if (a) b; else if (c) d; else if (e) f; else g"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f525e3671aa6d43caf17c2582f3c746f07570b7a..9fce9df9688253990d3fcfa4eb8f2280aa1c0c7c"
+ "shas": "0dc2b9999e933cc5f579be3de82aafbe951cd42c..0b04aed14c61bf7674a5161b0f0de2b45aa73c7d"
}
,{
"testCaseDescription": "javascript-if-else-delete-replacement-test",
@@ -700,7 +700,7 @@
],
"patch": [
"diff --git a/if-else.js b/if-else.js",
- "index 6bb0eaa..e26d6c4 100644",
+ "index 6bb0eaa7..e26d6c43 100644",
"--- a/if-else.js",
"+++ b/if-else.js",
"@@ -1,3 +1,2 @@",
@@ -710,7 +710,7 @@
"+if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9fce9df9688253990d3fcfa4eb8f2280aa1c0c7c..f5b900cb596f7084a32ca9441f01e9be4b1e27dd"
+ "shas": "0b04aed14c61bf7674a5161b0f0de2b45aa73c7d..805c0a73d13a58a939691a22c60cf60a9bf9ebe9"
}
,{
"testCaseDescription": "javascript-if-else-delete-test",
@@ -741,7 +741,7 @@
],
"patch": [
"diff --git a/if-else.js b/if-else.js",
- "index e26d6c4..1a55d0b 100644",
+ "index e26d6c43..1a55d0bd 100644",
"--- a/if-else.js",
"+++ b/if-else.js",
"@@ -1,2 +1 @@",
@@ -749,7 +749,7 @@
" if (g) h; else if (i) { j; } else if (k) l; else if (m) { n; } else o"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f5b900cb596f7084a32ca9441f01e9be4b1e27dd..c3bb4c6e35fc4755d18a5e0fb53d5410a476c039"
+ "shas": "805c0a73d13a58a939691a22c60cf60a9bf9ebe9..c61977d5bbe6b4469c6df78bfaeaff5caca6fa6f"
}
,{
"testCaseDescription": "javascript-if-else-delete-rest-test",
@@ -780,12 +780,12 @@
],
"patch": [
"diff --git a/if-else.js b/if-else.js",
- "index 1a55d0b..e69de29 100644",
+ "index 1a55d0bd..e69de29b 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",
- "shas": "c3bb4c6e35fc4755d18a5e0fb53d5410a476c039..dffe792710a5ad52de12ed62e48340a71e5c9227"
+ "shas": "c61977d5bbe6b4469c6df78bfaeaff5caca6fa6f..b0cccfc42d36aba8e42003998233c798245c627f"
}]
diff --git a/test/corpus/diff-summaries/javascript/if.json b/test/corpus/diff-summaries/javascript/if.json
index a4fd0fa51..2837b8289 100644
--- a/test/corpus/diff-summaries/javascript/if.json
+++ b/test/corpus/diff-summaries/javascript/if.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/if.js b/if.js",
- "index e69de29..52d4b4f 100644",
+ "index e69de29b..52d4b4f0 100644",
"--- a/if.js",
"+++ b/if.js",
"@@ -0,0 +1 @@",
"+if (x) { log(y); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4951403c16600a8ebe50779236bcbc480c823807..3ab04d08f09b5d896597f687046696c6cec1cf08"
+ "shas": "2440322c22f20e4b94216aa19cb2249a68864183..04f79bcb21f45b7628fee6124f78750926911c04"
}
,{
"testCaseDescription": "javascript-if-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/if.js b/if.js",
- "index 52d4b4f..ae4ee32 100644",
+ "index 52d4b4f0..ae4ee328 100644",
"--- a/if.js",
"+++ b/if.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" if (x) { log(y); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3ab04d08f09b5d896597f687046696c6cec1cf08..c5c2097ab589ca6e4187e2bae6455468ececcb93"
+ "shas": "04f79bcb21f45b7628fee6124f78750926911c04..559c420865a54f68f3b553b2a5da258f46f44883"
}
,{
"testCaseDescription": "javascript-if-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/if.js b/if.js",
- "index ae4ee32..df55832 100644",
+ "index ae4ee328..df55832d 100644",
"--- a/if.js",
"+++ b/if.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" if (x) { log(y); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c5c2097ab589ca6e4187e2bae6455468ececcb93..2f37518e72e7f3ea87111886870a575d8dc4369a"
+ "shas": "559c420865a54f68f3b553b2a5da258f46f44883..553c63f27c2226d27a3c8271282b468ef743e77b"
}
,{
"testCaseDescription": "javascript-if-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/if.js b/if.js",
- "index df55832..ae4ee32 100644",
+ "index df55832d..ae4ee328 100644",
"--- a/if.js",
"+++ b/if.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" if (x) { log(y); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2f37518e72e7f3ea87111886870a575d8dc4369a..3eaefb1b0937e7789aac874832358df33b530310"
+ "shas": "553c63f27c2226d27a3c8271282b468ef743e77b..c0a157045745524611f08863f811af735ec7661d"
}
,{
"testCaseDescription": "javascript-if-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/if.js b/if.js",
- "index ae4ee32..38b83ef 100644",
+ "index ae4ee328..38b83efe 100644",
"--- a/if.js",
"+++ b/if.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+if (a.b) { log(c); d; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3eaefb1b0937e7789aac874832358df33b530310..0e72c4d71d418eefb3726b7e5bc0232a5aad7db6"
+ "shas": "c0a157045745524611f08863f811af735ec7661d..3ed95396271b583c92b9c6fecb31bdd55c139fd6"
}
,{
"testCaseDescription": "javascript-if-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/if.js b/if.js",
- "index 38b83ef..f67163b 100644",
+ "index 38b83efe..f67163bb 100644",
"--- a/if.js",
"+++ b/if.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" if (a.b) { log(c); d; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0e72c4d71d418eefb3726b7e5bc0232a5aad7db6..b81dbad2ec8358dd3e22e71cca5eea1c286769a8"
+ "shas": "3ed95396271b583c92b9c6fecb31bdd55c139fd6..6705df9f639062177eaf9e73f3f265fb26a009e1"
}
,{
"testCaseDescription": "javascript-if-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/if.js b/if.js",
- "index f67163b..e69de29 100644",
+ "index f67163bb..e69de29b 100644",
"--- a/if.js",
"+++ b/if.js",
"@@ -1 +0,0 @@",
"-if (a.b) { log(c); d; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b81dbad2ec8358dd3e22e71cca5eea1c286769a8..ee538d5b471190fe27f80e1defc319f36f5f9c38"
+ "shas": "6705df9f639062177eaf9e73f3f265fb26a009e1..9b27e4158f8b990b3f7ca2f77fcf65bf40e26802"
}]
diff --git a/test/corpus/diff-summaries/javascript/import.json b/test/corpus/diff-summaries/javascript/import.json
index 0677c4d8f..6d4e8b7c3 100644
--- a/test/corpus/diff-summaries/javascript/import.json
+++ b/test/corpus/diff-summaries/javascript/import.json
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/import.js b/import.js",
- "index e69de29..491cb15 100644",
+ "index e69de29b..491cb15d 100644",
"--- a/import.js",
"+++ b/import.js",
"@@ -0,0 +1,8 @@",
@@ -146,7 +146,7 @@
"+import \"arctic-tern\";"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "94d7e0ef831c81697b130d8e7c032b876c270e33..bddd7205c75f938fdef876cad00d2a3130c8a056"
+ "shas": "22c469fbc95477137ad10d239a4f6a3c8ecd8aae..2d6475d95b8005bbedde47f63064877d878d1c4f"
}
,{
"testCaseDescription": "javascript-import-replacement-insert-test",
@@ -402,7 +402,7 @@
],
"patch": [
"diff --git a/import.js b/import.js",
- "index 491cb15..045c536 100644",
+ "index 491cb15d..045c536e 100644",
"--- a/import.js",
"+++ b/import.js",
"@@ -1,3 +1,19 @@",
@@ -427,7 +427,7 @@
" import { member } from \"ant\";"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "bddd7205c75f938fdef876cad00d2a3130c8a056..2f4516215b92d79082b1f806ec0ac74a2e18726c"
+ "shas": "2d6475d95b8005bbedde47f63064877d878d1c4f..1f40c3ca7170b24dd16bbb7fb042ce1221c48356"
}
,{
"testCaseDescription": "javascript-import-delete-insert-test",
@@ -701,7 +701,7 @@
],
"patch": [
"diff --git a/import.js b/import.js",
- "index 045c536..cbad5a4 100644",
+ "index 045c536e..cbad5a42 100644",
"--- a/import.js",
"+++ b/import.js",
"@@ -1,11 +1,11 @@",
@@ -726,7 +726,7 @@
" import { member } from \"ant\";"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2f4516215b92d79082b1f806ec0ac74a2e18726c..f6b32da510dd536120c67a2e13e3c5f17ca08a62"
+ "shas": "1f40c3ca7170b24dd16bbb7fb042ce1221c48356..06d730698c701308d886cc5ff2c45a30e421c469"
}
,{
"testCaseDescription": "javascript-import-replacement-test",
@@ -1000,7 +1000,7 @@
],
"patch": [
"diff --git a/import.js b/import.js",
- "index cbad5a4..045c536 100644",
+ "index cbad5a42..045c536e 100644",
"--- a/import.js",
"+++ b/import.js",
"@@ -1,11 +1,11 @@",
@@ -1025,7 +1025,7 @@
" import { member } from \"ant\";"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f6b32da510dd536120c67a2e13e3c5f17ca08a62..9d51ffb2d1950579de47c825eca14557ae9cefc8"
+ "shas": "06d730698c701308d886cc5ff2c45a30e421c469..920c660960691d88401f9399250f54e0453cb453"
}
,{
"testCaseDescription": "javascript-import-delete-replacement-test",
@@ -1401,7 +1401,7 @@
],
"patch": [
"diff --git a/import.js b/import.js",
- "index 045c536..873ff75 100644",
+ "index 045c536e..873ff752 100644",
"--- a/import.js",
"+++ b/import.js",
"@@ -1,19 +1,3 @@",
@@ -1438,7 +1438,7 @@
"+import \"basilisk\";"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9d51ffb2d1950579de47c825eca14557ae9cefc8..d8a44ed18d0fd2d59c8bfff2e97409d01face666"
+ "shas": "920c660960691d88401f9399250f54e0453cb453..627c6339717747333ab4223f2f9a660c1f9c22e7"
}
,{
"testCaseDescription": "javascript-import-delete-test",
@@ -1574,7 +1574,7 @@
],
"patch": [
"diff --git a/import.js b/import.js",
- "index 873ff75..db72339 100644",
+ "index 873ff752..db723392 100644",
"--- a/import.js",
"+++ b/import.js",
"@@ -1,11 +1,3 @@",
@@ -1591,7 +1591,7 @@
" import { element } from \"badger\";"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d8a44ed18d0fd2d59c8bfff2e97409d01face666..b5659554207c6b66f77467f2277c99b1686f8e02"
+ "shas": "627c6339717747333ab4223f2f9a660c1f9c22e7..7bf1e557d349101c8fe5544145db4836a629b057"
}
,{
"testCaseDescription": "javascript-import-delete-rest-test",
@@ -1727,7 +1727,7 @@
],
"patch": [
"diff --git a/import.js b/import.js",
- "index db72339..e69de29 100644",
+ "index db723392..e69de29b 100644",
"--- a/import.js",
"+++ b/import.js",
"@@ -1,8 +0,0 @@",
@@ -1741,5 +1741,5 @@
"-import \"basilisk\";"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b5659554207c6b66f77467f2277c99b1686f8e02..0eb14098d9cfc48fe7ffb44e37c71cb6cb58c878"
+ "shas": "7bf1e557d349101c8fe5544145db4836a629b057..b56108ab09b88f198a0ec68e4f7a87ad1b2c06b6"
}]
diff --git a/test/corpus/diff-summaries/javascript/math-assignment-operator.json b/test/corpus/diff-summaries/javascript/math-assignment-operator.json
index 1d72972f3..63c217230 100644
--- a/test/corpus/diff-summaries/javascript/math-assignment-operator.json
+++ b/test/corpus/diff-summaries/javascript/math-assignment-operator.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
- "index e69de29..7150d6e 100644",
+ "index e69de29b..7150d6e7 100644",
"--- a/math-assignment-operator.js",
"+++ b/math-assignment-operator.js",
"@@ -0,0 +1 @@",
"+x += 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5da04c6d20aa6fdedbc205bf855829ccd10687f3..5ec631f6610cf3cc1f773396df8e13b4b814129c"
+ "shas": "37c35686cb5d7f4301f701d97d4050125dffa916..1eca6b7e6dfd01b3f419dbbfc83fc728030526d5"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
- "index 7150d6e..0bf97e7 100644",
+ "index 7150d6e7..0bf97e75 100644",
"--- a/math-assignment-operator.js",
"+++ b/math-assignment-operator.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" x += 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5ec631f6610cf3cc1f773396df8e13b4b814129c..b0a185f38a22e6745bb368f017c102214337c4cb"
+ "shas": "1eca6b7e6dfd01b3f419dbbfc83fc728030526d5..a98d22dae5c746ed86c1413472e771fda438a6df"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
- "index 0bf97e7..ad04937 100644",
+ "index 0bf97e75..ad04937a 100644",
"--- a/math-assignment-operator.js",
"+++ b/math-assignment-operator.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" x += 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b0a185f38a22e6745bb368f017c102214337c4cb..38cc878f5583067ae28923541b036488434aff2b"
+ "shas": "a98d22dae5c746ed86c1413472e771fda438a6df..9949b25724f9edac4767ae26c9b063496761933d"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
- "index ad04937..0bf97e7 100644",
+ "index ad04937a..0bf97e75 100644",
"--- a/math-assignment-operator.js",
"+++ b/math-assignment-operator.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" x += 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "38cc878f5583067ae28923541b036488434aff2b..156edc8d14ab30f0157138c24b7694cec8a4bb67"
+ "shas": "9949b25724f9edac4767ae26c9b063496761933d..fbdb9aa0c8b68b4f99157885ea491b7800c8ba8a"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
- "index 0bf97e7..7127545 100644",
+ "index 0bf97e75..71275450 100644",
"--- a/math-assignment-operator.js",
"+++ b/math-assignment-operator.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+x += 2;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "156edc8d14ab30f0157138c24b7694cec8a4bb67..185343b45e80feb8176e8a5a0ee4ec9bbe0fb637"
+ "shas": "fbdb9aa0c8b68b4f99157885ea491b7800c8ba8a..6f1e2f449b202f9f7a061ef258b2c0c9f987cfe0"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
- "index 7127545..94d1472 100644",
+ "index 71275450..94d14722 100644",
"--- a/math-assignment-operator.js",
"+++ b/math-assignment-operator.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" x += 2;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "185343b45e80feb8176e8a5a0ee4ec9bbe0fb637..8ff3bab42e216d76eeba9d8c9c04f66c9c99eb7d"
+ "shas": "6f1e2f449b202f9f7a061ef258b2c0c9f987cfe0..470b9c6076966853b2ab55776d1cb7f09e0896ab"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/math-assignment-operator.js b/math-assignment-operator.js",
- "index 94d1472..e69de29 100644",
+ "index 94d14722..e69de29b 100644",
"--- a/math-assignment-operator.js",
"+++ b/math-assignment-operator.js",
"@@ -1 +0,0 @@",
"-x += 2;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8ff3bab42e216d76eeba9d8c9c04f66c9c99eb7d..1c2dbb18fb6fc930b3d0e6bb31a559a853be5c63"
+ "shas": "470b9c6076966853b2ab55776d1cb7f09e0896ab..a7b8d1dcde9a2945edc002250d8df6d841189c39"
}]
diff --git a/test/corpus/diff-summaries/javascript/math-operator.json b/test/corpus/diff-summaries/javascript/math-operator.json
index 13e75eb52..608582e86 100644
--- a/test/corpus/diff-summaries/javascript/math-operator.json
+++ b/test/corpus/diff-summaries/javascript/math-operator.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/math-operator.js b/math-operator.js",
- "index e69de29..0344667 100644",
+ "index e69de29b..03446677 100644",
"--- a/math-operator.js",
"+++ b/math-operator.js",
"@@ -0,0 +1 @@",
"+i + j * 3 - j % 5;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "41ab7cb7dc378bf229f7a08f1a03c0676483f435..1571de07c19283348c86a4d81f61c63270a37d3f"
+ "shas": "6c2a6d2038e58ffec3265d64973449c3c258d5ad..5cc9b010912a3ee08aaf18f3beafedd31740b011"
}
,{
"testCaseDescription": "javascript-math-operator-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/math-operator.js b/math-operator.js",
- "index 0344667..79f5f20 100644",
+ "index 03446677..79f5f20c 100644",
"--- a/math-operator.js",
"+++ b/math-operator.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" i + j * 3 - j % 5;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1571de07c19283348c86a4d81f61c63270a37d3f..97979c27333f35afb7288063c45a2f25cf5e1808"
+ "shas": "5cc9b010912a3ee08aaf18f3beafedd31740b011..3da1355235d8d4fec9a54cefcf11f9536cfad9fe"
}
,{
"testCaseDescription": "javascript-math-operator-delete-insert-test",
@@ -159,7 +159,7 @@
],
"patch": [
"diff --git a/math-operator.js b/math-operator.js",
- "index 79f5f20..284561c 100644",
+ "index 79f5f20c..284561c5 100644",
"--- a/math-operator.js",
"+++ b/math-operator.js",
"@@ -1,3 +1,3 @@",
@@ -169,7 +169,7 @@
" i + j * 3 - j % 5;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "97979c27333f35afb7288063c45a2f25cf5e1808..d8320eb8219fb470d6ac17996f9d74b61fe7e6ee"
+ "shas": "3da1355235d8d4fec9a54cefcf11f9536cfad9fe..566c62a4a59091e26052615274a13a04d2b00401"
}
,{
"testCaseDescription": "javascript-math-operator-replacement-test",
@@ -239,7 +239,7 @@
],
"patch": [
"diff --git a/math-operator.js b/math-operator.js",
- "index 284561c..79f5f20 100644",
+ "index 284561c5..79f5f20c 100644",
"--- a/math-operator.js",
"+++ b/math-operator.js",
"@@ -1,3 +1,3 @@",
@@ -249,7 +249,7 @@
" i + j * 3 - j % 5;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d8320eb8219fb470d6ac17996f9d74b61fe7e6ee..ca05a18c434755562d8787734dd2aa347af4ffca"
+ "shas": "566c62a4a59091e26052615274a13a04d2b00401..e44f1851599323aed0e6c491558936211b2815fc"
}
,{
"testCaseDescription": "javascript-math-operator-delete-replacement-test",
@@ -310,7 +310,7 @@
],
"patch": [
"diff --git a/math-operator.js b/math-operator.js",
- "index 79f5f20..d1055f7 100644",
+ "index 79f5f20c..d1055f77 100644",
"--- a/math-operator.js",
"+++ b/math-operator.js",
"@@ -1,3 +1,2 @@",
@@ -320,7 +320,7 @@
"+i + j * 2 - j % 4;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ca05a18c434755562d8787734dd2aa347af4ffca..4f0d2886b18d7b66ad3b3d0222b5c4040ebfbf05"
+ "shas": "e44f1851599323aed0e6c491558936211b2815fc..1a7ef2981311a4aed0e0591a526b8ef78ee190f7"
}
,{
"testCaseDescription": "javascript-math-operator-delete-test",
@@ -351,7 +351,7 @@
],
"patch": [
"diff --git a/math-operator.js b/math-operator.js",
- "index d1055f7..79ba2b3 100644",
+ "index d1055f77..79ba2b3f 100644",
"--- a/math-operator.js",
"+++ b/math-operator.js",
"@@ -1,2 +1 @@",
@@ -359,7 +359,7 @@
" i + j * 2 - j % 4;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4f0d2886b18d7b66ad3b3d0222b5c4040ebfbf05..c7c1c352742d04515a004d1c08642b78cf1e83cf"
+ "shas": "1a7ef2981311a4aed0e0591a526b8ef78ee190f7..544ee219892710050b020798ca49e15208a7c028"
}
,{
"testCaseDescription": "javascript-math-operator-delete-rest-test",
@@ -390,12 +390,12 @@
],
"patch": [
"diff --git a/math-operator.js b/math-operator.js",
- "index 79ba2b3..e69de29 100644",
+ "index 79ba2b3f..e69de29b 100644",
"--- a/math-operator.js",
"+++ b/math-operator.js",
"@@ -1 +0,0 @@",
"-i + j * 2 - j % 4;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c7c1c352742d04515a004d1c08642b78cf1e83cf..69248e3fdb3e6ab7da864ef7bd3a915aeefd3cc4"
+ "shas": "544ee219892710050b020798ca49e15208a7c028..68249c6faa764e8f289c3ae7afb4c98267e953d8"
}]
diff --git a/test/corpus/diff-summaries/javascript/member-access-assignment.json b/test/corpus/diff-summaries/javascript/member-access-assignment.json
index 797cabc82..a5ebc6a7a 100644
--- a/test/corpus/diff-summaries/javascript/member-access-assignment.json
+++ b/test/corpus/diff-summaries/javascript/member-access-assignment.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/member-access-assignment.js b/member-access-assignment.js",
- "index e69de29..7a99e30 100644",
+ "index e69de29b..7a99e309 100644",
"--- a/member-access-assignment.js",
"+++ b/member-access-assignment.js",
"@@ -0,0 +1 @@",
"+y.x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "83f3153b76f49e077237997c965dc6f3c3a159bc..e3b5bd418d494825d815573a2dd33bb71bee5d48"
+ "shas": "8971dc3263a4d4060368d23937d32f6df7c06d16..4e88541e19df2f302cf1337af08f45198be7859b"
}
,{
"testCaseDescription": "javascript-member-access-assignment-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/member-access-assignment.js b/member-access-assignment.js",
- "index 7a99e30..3204006 100644",
+ "index 7a99e309..32040068 100644",
"--- a/member-access-assignment.js",
"+++ b/member-access-assignment.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" y.x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "e3b5bd418d494825d815573a2dd33bb71bee5d48..1da355d7b96efcfa960001b22e4bc94e5be102bd"
+ "shas": "4e88541e19df2f302cf1337af08f45198be7859b..a95a09675d9fe9e0d6e296b6527a4c7481e8cf55"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/member-access-assignment.js b/member-access-assignment.js",
- "index 3204006..94893a3 100644",
+ "index 32040068..94893a32 100644",
"--- a/member-access-assignment.js",
"+++ b/member-access-assignment.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" y.x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1da355d7b96efcfa960001b22e4bc94e5be102bd..f2443f2327ec99428bb7538077575ea11136f8bd"
+ "shas": "a95a09675d9fe9e0d6e296b6527a4c7481e8cf55..34a3e46f6598a923b2e78e0f012dfbe4faac797d"
}
,{
"testCaseDescription": "javascript-member-access-assignment-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/member-access-assignment.js b/member-access-assignment.js",
- "index 94893a3..3204006 100644",
+ "index 94893a32..32040068 100644",
"--- a/member-access-assignment.js",
"+++ b/member-access-assignment.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" y.x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f2443f2327ec99428bb7538077575ea11136f8bd..396adf86163adae31b6cbe282ed485497c4f42a4"
+ "shas": "34a3e46f6598a923b2e78e0f012dfbe4faac797d..54b9c38305d1c90e6c97ec2c89f6aa125c038f15"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/member-access-assignment.js b/member-access-assignment.js",
- "index 3204006..8d78a24 100644",
+ "index 32040068..8d78a24f 100644",
"--- a/member-access-assignment.js",
"+++ b/member-access-assignment.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+y.x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "396adf86163adae31b6cbe282ed485497c4f42a4..ebd783b11d81b4c31d3883606aa0ee7019afb1c3"
+ "shas": "54b9c38305d1c90e6c97ec2c89f6aa125c038f15..21b4c15a34c4279184e291cdd81eae4d5c35f565"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/member-access-assignment.js b/member-access-assignment.js",
- "index 8d78a24..799018d 100644",
+ "index 8d78a24f..799018d0 100644",
"--- a/member-access-assignment.js",
"+++ b/member-access-assignment.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" y.x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ebd783b11d81b4c31d3883606aa0ee7019afb1c3..f0a86404c7e04e9a627fd8464879a14361a379bd"
+ "shas": "21b4c15a34c4279184e291cdd81eae4d5c35f565..93b31824234e8cd04d5e25e83a17d059e8c005b7"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/member-access-assignment.js b/member-access-assignment.js",
- "index 799018d..e69de29 100644",
+ "index 799018d0..e69de29b 100644",
"--- a/member-access-assignment.js",
"+++ b/member-access-assignment.js",
"@@ -1 +0,0 @@",
"-y.x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f0a86404c7e04e9a627fd8464879a14361a379bd..faf582893e706ae259a0482d65d424fbcf137bb2"
+ "shas": "93b31824234e8cd04d5e25e83a17d059e8c005b7..4771589971576b44762a611a7b4b4cbdb9259735"
}]
diff --git a/test/corpus/diff-summaries/javascript/member-access.json b/test/corpus/diff-summaries/javascript/member-access.json
index 186a73d2c..98401727b 100644
--- a/test/corpus/diff-summaries/javascript/member-access.json
+++ b/test/corpus/diff-summaries/javascript/member-access.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/member-access.js b/member-access.js",
- "index e69de29..3c837c9 100644",
+ "index e69de29b..3c837c9a 100644",
"--- a/member-access.js",
"+++ b/member-access.js",
"@@ -0,0 +1 @@",
"+x.someProperty;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0cbc55e481f01ab536c7832c5ebbc21d7f9e9021..9a5f4f1bbfa04d4b229b51802ca72129a31b1953"
+ "shas": "5465664fb6e49eb214afa9feb0fadd451399dad9..fbdf589ce4b68c6eb2c32f0caf1f5a98977575dd"
}
,{
"testCaseDescription": "javascript-member-access-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/member-access.js b/member-access.js",
- "index 3c837c9..858131a 100644",
+ "index 3c837c9a..858131af 100644",
"--- a/member-access.js",
"+++ b/member-access.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" x.someProperty;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9a5f4f1bbfa04d4b229b51802ca72129a31b1953..93677ca22426294b752c658707b4052a3a3220ed"
+ "shas": "fbdf589ce4b68c6eb2c32f0caf1f5a98977575dd..4af60582c01401af8e4fb5440ebf9a27278743d3"
}
,{
"testCaseDescription": "javascript-member-access-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/member-access.js b/member-access.js",
- "index 858131a..5ed8a8d 100644",
+ "index 858131af..5ed8a8d2 100644",
"--- a/member-access.js",
"+++ b/member-access.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" x.someProperty;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "93677ca22426294b752c658707b4052a3a3220ed..df73936014819634cde8e6741fef45116b094d93"
+ "shas": "4af60582c01401af8e4fb5440ebf9a27278743d3..d7c2b4243cc835256891d23b8ac815bf2c8100fd"
}
,{
"testCaseDescription": "javascript-member-access-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/member-access.js b/member-access.js",
- "index 5ed8a8d..858131a 100644",
+ "index 5ed8a8d2..858131af 100644",
"--- a/member-access.js",
"+++ b/member-access.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" x.someProperty;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "df73936014819634cde8e6741fef45116b094d93..94c28d92c27008e7f21ed463e683fdfbda0b8287"
+ "shas": "d7c2b4243cc835256891d23b8ac815bf2c8100fd..fe939d7cf2c040cbe7a3c0e2ba5ce50beb5b00eb"
}
,{
"testCaseDescription": "javascript-member-access-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/member-access.js b/member-access.js",
- "index 858131a..81f5f46 100644",
+ "index 858131af..81f5f468 100644",
"--- a/member-access.js",
"+++ b/member-access.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+x.someOtherProperty"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "94c28d92c27008e7f21ed463e683fdfbda0b8287..38ee25545f8644cee42edb45ef2f7b29b26892d5"
+ "shas": "fe939d7cf2c040cbe7a3c0e2ba5ce50beb5b00eb..5e0221213de5c8eb25ac5751117b6e9632b32e2f"
}
,{
"testCaseDescription": "javascript-member-access-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/member-access.js b/member-access.js",
- "index 81f5f46..8329c77 100644",
+ "index 81f5f468..8329c770 100644",
"--- a/member-access.js",
"+++ b/member-access.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" x.someOtherProperty"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "38ee25545f8644cee42edb45ef2f7b29b26892d5..6188b94ce3872e80b40738d01c4853a467d502c2"
+ "shas": "5e0221213de5c8eb25ac5751117b6e9632b32e2f..8ab246f4bfdc85fc189921ae13ea91f0a9bae27e"
}
,{
"testCaseDescription": "javascript-member-access-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/member-access.js b/member-access.js",
- "index 8329c77..e69de29 100644",
+ "index 8329c770..e69de29b 100644",
"--- a/member-access.js",
"+++ b/member-access.js",
"@@ -1 +0,0 @@",
"-x.someOtherProperty"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6188b94ce3872e80b40738d01c4853a467d502c2..bcba202e709aea072f614c126e2a5bb356cbf3fe"
+ "shas": "8ab246f4bfdc85fc189921ae13ea91f0a9bae27e..9043f23503e9e2afefc8849bfc0831696797e235"
}]
diff --git a/test/corpus/diff-summaries/javascript/method-call.json b/test/corpus/diff-summaries/javascript/method-call.json
index 847d35bae..ff486acad 100644
--- a/test/corpus/diff-summaries/javascript/method-call.json
+++ b/test/corpus/diff-summaries/javascript/method-call.json
@@ -16,7 +16,7 @@
]
}
},
- "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call"
+ "summary": "Added the 'object.someMethod(arg1, \"arg2\")' function call"
}
]
},
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/method-call.js b/method-call.js",
- "index e69de29..07ab90c 100644",
+ "index e69de29b..07ab90c6 100644",
"--- a/method-call.js",
"+++ b/method-call.js",
"@@ -0,0 +1 @@",
"+object.someMethod(arg1, \"arg2\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f8662860eb083b9e95b5cc1c706a7872a4779532..616ca3e3b4a298f69107bd17d20b8fe2e5fd3d80"
+ "shas": "bded2c0215b6dc80127e031b7d9978f1883709b1..5627add826bf77a4699b8cdb8d3993eb3a9e4662"
}
,{
"testCaseDescription": "javascript-method-call-replacement-insert-test",
@@ -54,7 +54,7 @@
]
}
},
- "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call"
+ "summary": "Added the 'object.someMethod(arg1, \"arg3\")' function call"
},
{
"span": {
@@ -69,7 +69,7 @@
]
}
},
- "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call"
+ "summary": "Added the 'object.someMethod(arg1, \"arg2\")' function call"
}
]
},
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/method-call.js b/method-call.js",
- "index 07ab90c..9341e17 100644",
+ "index 07ab90c6..9341e175 100644",
"--- a/method-call.js",
"+++ b/method-call.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" object.someMethod(arg1, \"arg2\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "616ca3e3b4a298f69107bd17d20b8fe2e5fd3d80..1ddf2d53694021927a1783fc78ab68dca0508ce9"
+ "shas": "5627add826bf77a4699b8cdb8d3993eb3a9e4662..11b38abc49718f3cb71c61270fcefa4977359edb"
}
,{
"testCaseDescription": "javascript-method-call-delete-insert-test",
@@ -121,7 +121,7 @@
}
]
},
- "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the object.someMethod(arg1, \"arg2\") method call"
+ "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the object.someMethod(arg1, \"arg2\") function call"
}
]
},
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/method-call.js b/method-call.js",
- "index 9341e17..f6ada2d 100644",
+ "index 9341e175..f6ada2d1 100644",
"--- a/method-call.js",
"+++ b/method-call.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" object.someMethod(arg1, \"arg2\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1ddf2d53694021927a1783fc78ab68dca0508ce9..741134e42738870aeb25a8395d4a656ddd86bf4b"
+ "shas": "11b38abc49718f3cb71c61270fcefa4977359edb..713aff1ea9523bf8f586f6717040a9be57b190cc"
}
,{
"testCaseDescription": "javascript-method-call-replacement-test",
@@ -174,7 +174,7 @@
}
]
},
- "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the object.someMethod(arg1, \"arg3\") method call"
+ "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the object.someMethod(arg1, \"arg3\") function call"
}
]
},
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/method-call.js b/method-call.js",
- "index f6ada2d..9341e17 100644",
+ "index f6ada2d1..9341e175 100644",
"--- a/method-call.js",
"+++ b/method-call.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" object.someMethod(arg1, \"arg2\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "741134e42738870aeb25a8395d4a656ddd86bf4b..4778b03d41ac4397158cf93d091d520be85bfc34"
+ "shas": "713aff1ea9523bf8f586f6717040a9be57b190cc..b43eacb14e34c4e0bb0d4b5a8381f5271b67e013"
}
,{
"testCaseDescription": "javascript-method-call-delete-replacement-test",
@@ -215,7 +215,7 @@
]
}
},
- "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call"
+ "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' function call"
},
{
"span": {
@@ -230,7 +230,7 @@
]
}
},
- "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call"
+ "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' function call"
},
{
"span": {
@@ -245,7 +245,7 @@
]
}
},
- "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call"
+ "summary": "Added the 'object.someMethod(arg1, \"arg3\")' function call"
}
]
},
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/method-call.js b/method-call.js",
- "index 9341e17..894dcf6 100644",
+ "index 9341e175..894dcf66 100644",
"--- a/method-call.js",
"+++ b/method-call.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+object.someMethod(arg1, \"arg3\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4778b03d41ac4397158cf93d091d520be85bfc34..b2b8e482425d3459e6e1cab14dd7c6201bfa516e"
+ "shas": "b43eacb14e34c4e0bb0d4b5a8381f5271b67e013..a2c1a597cf54b56f5bd3ee6cdc19865d28826f50"
}
,{
"testCaseDescription": "javascript-method-call-delete-test",
@@ -286,7 +286,7 @@
]
}
},
- "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call"
+ "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' function call"
}
]
},
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/method-call.js b/method-call.js",
- "index 894dcf6..a82528c 100644",
+ "index 894dcf66..a82528c8 100644",
"--- a/method-call.js",
"+++ b/method-call.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" object.someMethod(arg1, \"arg3\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b2b8e482425d3459e6e1cab14dd7c6201bfa516e..54e0a5e18b235909c85caf03159b380559d9c68d"
+ "shas": "a2c1a597cf54b56f5bd3ee6cdc19865d28826f50..52ee491ebe644b6cf1a0380abc94dff8b4b48fd6"
}
,{
"testCaseDescription": "javascript-method-call-delete-rest-test",
@@ -325,7 +325,7 @@
]
}
},
- "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call"
+ "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' function call"
}
]
},
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/method-call.js b/method-call.js",
- "index a82528c..e69de29 100644",
+ "index a82528c8..e69de29b 100644",
"--- a/method-call.js",
"+++ b/method-call.js",
"@@ -1 +0,0 @@",
"-object.someMethod(arg1, \"arg3\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "54e0a5e18b235909c85caf03159b380559d9c68d..5d5d40b2fa515dfcb7494d9b83f22687c56de0f5"
+ "shas": "52ee491ebe644b6cf1a0380abc94dff8b4b48fd6..ff5044f4617b79b896e8da9c860b589d4022aa5b"
}]
diff --git a/test/corpus/diff-summaries/javascript/named-function.json b/test/corpus/diff-summaries/javascript/named-function.json
index 03ecda93a..ba192c7c2 100644
--- a/test/corpus/diff-summaries/javascript/named-function.json
+++ b/test/corpus/diff-summaries/javascript/named-function.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/named-function.js b/named-function.js",
- "index e69de29..94b19f8 100644",
+ "index e69de29b..94b19f8e 100644",
"--- a/named-function.js",
"+++ b/named-function.js",
"@@ -0,0 +1 @@",
"+function myFunction(arg1, arg2) { arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "973cce7b94116a9e6e8b399f9f0a50bd107fb9b5..0af41b91893fcc8e9172616a4e5a71c70ee47985"
+ "shas": "35363e93d3151d395860548f66a39be33fcc6b34..79a23a83c739d0cfa28d7a169a6bf7da60e491a0"
}
,{
"testCaseDescription": "javascript-named-function-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/named-function.js b/named-function.js",
- "index 94b19f8..cb766a0 100644",
+ "index 94b19f8e..cb766a0e 100644",
"--- a/named-function.js",
"+++ b/named-function.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" function myFunction(arg1, arg2) { arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0af41b91893fcc8e9172616a4e5a71c70ee47985..2fe69bd38fe1db507331dc14063479b66eb2a880"
+ "shas": "79a23a83c739d0cfa28d7a169a6bf7da60e491a0..a4d27609f597d097c760a7cc1b472df19e639346"
}
,{
"testCaseDescription": "javascript-named-function-delete-insert-test",
@@ -192,7 +192,7 @@
],
"patch": [
"diff --git a/named-function.js b/named-function.js",
- "index cb766a0..c9cff07 100644",
+ "index cb766a0e..c9cff077 100644",
"--- a/named-function.js",
"+++ b/named-function.js",
"@@ -1,3 +1,3 @@",
@@ -202,7 +202,7 @@
" function myFunction(arg1, arg2) { arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2fe69bd38fe1db507331dc14063479b66eb2a880..4b0a0bcf80003eb74b67b8947f8a0443cb2ad80f"
+ "shas": "a4d27609f597d097c760a7cc1b472df19e639346..8d31ee951cafd297a9e905803bd5b2bc56c2f630"
}
,{
"testCaseDescription": "javascript-named-function-replacement-test",
@@ -305,7 +305,7 @@
],
"patch": [
"diff --git a/named-function.js b/named-function.js",
- "index c9cff07..cb766a0 100644",
+ "index c9cff077..cb766a0e 100644",
"--- a/named-function.js",
"+++ b/named-function.js",
"@@ -1,3 +1,3 @@",
@@ -315,7 +315,7 @@
" function myFunction(arg1, arg2) { arg2; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4b0a0bcf80003eb74b67b8947f8a0443cb2ad80f..785a621c11eb5f6e1e93d2ea1e40828c8786ae2d"
+ "shas": "8d31ee951cafd297a9e905803bd5b2bc56c2f630..69e6312b3a109336408f27d7e8be8f73d8755a00"
}
,{
"testCaseDescription": "javascript-named-function-delete-replacement-test",
@@ -376,7 +376,7 @@
],
"patch": [
"diff --git a/named-function.js b/named-function.js",
- "index cb766a0..148bcc7 100644",
+ "index cb766a0e..148bcc77 100644",
"--- a/named-function.js",
"+++ b/named-function.js",
"@@ -1,3 +1,2 @@",
@@ -386,7 +386,7 @@
"+function anotherFunction() { return false; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "785a621c11eb5f6e1e93d2ea1e40828c8786ae2d..7ecdd3334fd0090f017044bd0780b5a5df128eda"
+ "shas": "69e6312b3a109336408f27d7e8be8f73d8755a00..47634c570fdbb43851ac8f35d7ba6533aa1560d5"
}
,{
"testCaseDescription": "javascript-named-function-delete-test",
@@ -417,7 +417,7 @@
],
"patch": [
"diff --git a/named-function.js b/named-function.js",
- "index 148bcc7..80e11b0 100644",
+ "index 148bcc77..80e11b02 100644",
"--- a/named-function.js",
"+++ b/named-function.js",
"@@ -1,2 +1 @@",
@@ -425,7 +425,7 @@
" function anotherFunction() { return false; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7ecdd3334fd0090f017044bd0780b5a5df128eda..92cb451c62ab6f9a63bad5a24b21beb2cbe9bdde"
+ "shas": "47634c570fdbb43851ac8f35d7ba6533aa1560d5..0062e2d432f2030721aa50d3a3655d3d3230d2a8"
}
,{
"testCaseDescription": "javascript-named-function-delete-rest-test",
@@ -456,12 +456,12 @@
],
"patch": [
"diff --git a/named-function.js b/named-function.js",
- "index 80e11b0..e69de29 100644",
+ "index 80e11b02..e69de29b 100644",
"--- a/named-function.js",
"+++ b/named-function.js",
"@@ -1 +0,0 @@",
"-function anotherFunction() { return false; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "92cb451c62ab6f9a63bad5a24b21beb2cbe9bdde..0cbc55e481f01ab536c7832c5ebbc21d7f9e9021"
+ "shas": "0062e2d432f2030721aa50d3a3655d3d3230d2a8..5465664fb6e49eb214afa9feb0fadd451399dad9"
}]
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 a0aa38dcc..c4e4afcf1 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
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
- "index e69de29..d205614 100644",
+ "index e69de29b..d205614e 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",
- "shas": "b916dd0d4e57f46f672acd9dc9130eef9e0bcc60..b60cbbceaf5939517572a1c7ebc7fd80db858b96"
+ "shas": "d15a8f422c2a2393c71f113fdb716151dc5a3840..b4a17d8d80eb1f61e6164fbeee64f743901c5f4a"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
- "index d205614..5dfcca6 100644",
+ "index d205614e..5dfcca69 100644",
"--- a/nested-do-while-in-function.js",
"+++ b/nested-do-while-in-function.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" function f(arg1, arg2) { do { something(arg1); } while (arg2); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b60cbbceaf5939517572a1c7ebc7fd80db858b96..3da97953dcda4f775d102a777c46bf8476ac6ee6"
+ "shas": "b4a17d8d80eb1f61e6164fbeee64f743901c5f4a..d125a2d3ebde11882a9a1539258c02087154c194"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-insert-test",
@@ -159,7 +159,7 @@
],
"patch": [
"diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
- "index 5dfcca6..49cff7e 100644",
+ "index 5dfcca69..49cff7e6 100644",
"--- a/nested-do-while-in-function.js",
"+++ b/nested-do-while-in-function.js",
"@@ -1,3 +1,3 @@",
@@ -169,7 +169,7 @@
" function f(arg1, arg2) { do { something(arg1); } while (arg2); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3da97953dcda4f775d102a777c46bf8476ac6ee6..d91742e7e9daa195667f006f6eb20e19c6f16c00"
+ "shas": "d125a2d3ebde11882a9a1539258c02087154c194..9c889d3b83c7228151ed4c83ab806f8060ffb00d"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-replacement-test",
@@ -239,7 +239,7 @@
],
"patch": [
"diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
- "index 49cff7e..5dfcca6 100644",
+ "index 49cff7e6..5dfcca69 100644",
"--- a/nested-do-while-in-function.js",
"+++ b/nested-do-while-in-function.js",
"@@ -1,3 +1,3 @@",
@@ -249,7 +249,7 @@
" function f(arg1, arg2) { do { something(arg1); } while (arg2); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d91742e7e9daa195667f006f6eb20e19c6f16c00..f4842813b2ac2a5996ad23bbeeb6d022a3c29f8e"
+ "shas": "9c889d3b83c7228151ed4c83ab806f8060ffb00d..c4b51ed8e19eeecba520893a9b39cf91470ffe2e"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-replacement-test",
@@ -310,7 +310,7 @@
],
"patch": [
"diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
- "index 5dfcca6..babb1e6 100644",
+ "index 5dfcca69..babb1e64 100644",
"--- a/nested-do-while-in-function.js",
"+++ b/nested-do-while-in-function.js",
"@@ -1,3 +1,2 @@",
@@ -320,7 +320,7 @@
"+function f(arg1, arg2) { do { something(arg2); } while (arg1); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f4842813b2ac2a5996ad23bbeeb6d022a3c29f8e..39c63fc4aa834c62a569d089f3c660ff87519271"
+ "shas": "c4b51ed8e19eeecba520893a9b39cf91470ffe2e..e199bde1293a13976d3235e02d7ceb234e17d481"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-test",
@@ -351,7 +351,7 @@
],
"patch": [
"diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
- "index babb1e6..2b15580 100644",
+ "index babb1e64..2b155808 100644",
"--- a/nested-do-while-in-function.js",
"+++ b/nested-do-while-in-function.js",
"@@ -1,2 +1 @@",
@@ -359,7 +359,7 @@
" function f(arg1, arg2) { do { something(arg2); } while (arg1); }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "39c63fc4aa834c62a569d089f3c660ff87519271..6cdad31d7f48683bfe6ff831cd286c79d2467e8f"
+ "shas": "e199bde1293a13976d3235e02d7ceb234e17d481..4e731827e9cb06d636d745aceb4ef4e616be8bd1"
}
,{
"testCaseDescription": "javascript-nested-do-while-in-function-delete-rest-test",
@@ -390,12 +390,12 @@
],
"patch": [
"diff --git a/nested-do-while-in-function.js b/nested-do-while-in-function.js",
- "index 2b15580..e69de29 100644",
+ "index 2b155808..e69de29b 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",
- "shas": "6cdad31d7f48683bfe6ff831cd286c79d2467e8f..94d7e0ef831c81697b130d8e7c032b876c270e33"
+ "shas": "4e731827e9cb06d636d745aceb4ef4e616be8bd1..22c469fbc95477137ad10d239a4f6a3c8ecd8aae"
}]
diff --git a/test/corpus/diff-summaries/javascript/nested-functions.json b/test/corpus/diff-summaries/javascript/nested-functions.json
index 3fecd1805..60aaad4ce 100644
--- a/test/corpus/diff-summaries/javascript/nested-functions.json
+++ b/test/corpus/diff-summaries/javascript/nested-functions.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/nested-functions.js b/nested-functions.js",
- "index e69de29..72531d8 100644",
+ "index e69de29b..72531d81 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",
- "shas": "d1b2bee18a7da4fefa2a4786b2f692fc5795f48c..71dc5237f7ffca394739d3f93487a7187b0a12a8"
+ "shas": "03a1b4a15f149e9715aa37bf2334cb4f05f0e8ff..4ce42b8934b35777d212723ca9a88cbee7535b48"
}
,{
"testCaseDescription": "javascript-nested-functions-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/nested-functions.js b/nested-functions.js",
- "index 72531d8..c960aae 100644",
+ "index 72531d81..c960aae1 100644",
"--- a/nested-functions.js",
"+++ b/nested-functions.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "71dc5237f7ffca394739d3f93487a7187b0a12a8..7e5b3b060a63fde4ac14ad0902c3cfa453e7342e"
+ "shas": "4ce42b8934b35777d212723ca9a88cbee7535b48..d4b753c9830ac2dd22f16d0ec57c93b3214d7d57"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-insert-test",
@@ -121,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'arg1' identifier with the 'arg3' identifier in the console.log(arg3) method call of the 'child' function"
+ "summary": "Replaced the 'arg1' identifier with the 'arg3' identifier in the console.log(arg3) function call of the 'child' function"
},
{
"span": {
@@ -148,7 +148,7 @@
}
]
},
- "summary": "Replaced the 'arg2' identifier with the 'arg4' identifier in the console.log(arg4) method call of the 'child' function"
+ "summary": "Replaced the 'arg2' identifier with the 'arg4' identifier in the console.log(arg4) function call of the 'child' function"
}
]
},
@@ -159,7 +159,7 @@
],
"patch": [
"diff --git a/nested-functions.js b/nested-functions.js",
- "index c960aae..1b9b61a 100644",
+ "index c960aae1..1b9b61a3 100644",
"--- a/nested-functions.js",
"+++ b/nested-functions.js",
"@@ -1,3 +1,3 @@",
@@ -169,7 +169,7 @@
" function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7e5b3b060a63fde4ac14ad0902c3cfa453e7342e..ca415e38a948a4c4de9d07e37c1c9cfc34d8445c"
+ "shas": "d4b753c9830ac2dd22f16d0ec57c93b3214d7d57..27d1213c9b03406885e69e99e21581bdc0d57a90"
}
,{
"testCaseDescription": "javascript-nested-functions-replacement-test",
@@ -201,7 +201,7 @@
}
]
},
- "summary": "Replaced the 'arg3' identifier with the 'arg1' identifier in the console.log(arg1) method call of the 'child' function"
+ "summary": "Replaced the 'arg3' identifier with the 'arg1' identifier in the console.log(arg1) function call of the 'child' function"
},
{
"span": {
@@ -228,7 +228,7 @@
}
]
},
- "summary": "Replaced the 'arg4' identifier with the 'arg2' identifier in the console.log(arg2) method call of the 'child' function"
+ "summary": "Replaced the 'arg4' identifier with the 'arg2' identifier in the console.log(arg2) function call of the 'child' function"
}
]
},
@@ -239,7 +239,7 @@
],
"patch": [
"diff --git a/nested-functions.js b/nested-functions.js",
- "index 1b9b61a..c960aae 100644",
+ "index 1b9b61a3..c960aae1 100644",
"--- a/nested-functions.js",
"+++ b/nested-functions.js",
"@@ -1,3 +1,3 @@",
@@ -249,7 +249,7 @@
" function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ca415e38a948a4c4de9d07e37c1c9cfc34d8445c..2c630214d8f19ee0f2818b939a13a27d703d2b17"
+ "shas": "27d1213c9b03406885e69e99e21581bdc0d57a90..b4cc03a33f7f1b03461ad9089715eba1f44ede40"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-replacement-test",
@@ -310,7 +310,7 @@
],
"patch": [
"diff --git a/nested-functions.js b/nested-functions.js",
- "index c960aae..81522c7 100644",
+ "index c960aae1..81522c7d 100644",
"--- a/nested-functions.js",
"+++ b/nested-functions.js",
"@@ -1,3 +1,2 @@",
@@ -320,7 +320,7 @@
"+function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2c630214d8f19ee0f2818b939a13a27d703d2b17..8d2f83fd46bff59083e96ad5e3f2840603171027"
+ "shas": "b4cc03a33f7f1b03461ad9089715eba1f44ede40..dc0c846188cd94a7a6c54e6ffeb8a2df5954cf20"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-test",
@@ -351,7 +351,7 @@
],
"patch": [
"diff --git a/nested-functions.js b/nested-functions.js",
- "index 81522c7..3056480 100644",
+ "index 81522c7d..30564800 100644",
"--- a/nested-functions.js",
"+++ b/nested-functions.js",
"@@ -1,2 +1 @@",
@@ -359,7 +359,7 @@
" function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8d2f83fd46bff59083e96ad5e3f2840603171027..13f268f35a3fde68001653b29f9e0eb0568c4d14"
+ "shas": "dc0c846188cd94a7a6c54e6ffeb8a2df5954cf20..7d1d6d109a4c86188cdfb9df514d7f3bf1009ae8"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-rest-test",
@@ -390,12 +390,12 @@
],
"patch": [
"diff --git a/nested-functions.js b/nested-functions.js",
- "index 3056480..e69de29 100644",
+ "index 30564800..e69de29b 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",
- "shas": "13f268f35a3fde68001653b29f9e0eb0568c4d14..b916dd0d4e57f46f672acd9dc9130eef9e0bcc60"
+ "shas": "7d1d6d109a4c86188cdfb9df514d7f3bf1009ae8..d15a8f422c2a2393c71f113fdb716151dc5a3840"
}]
diff --git a/test/corpus/diff-summaries/javascript/null.json b/test/corpus/diff-summaries/javascript/null.json
index 9a5c8f7fd..f5035e1c7 100644
--- a/test/corpus/diff-summaries/javascript/null.json
+++ b/test/corpus/diff-summaries/javascript/null.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/null.js b/null.js",
- "index e69de29..ff464d1 100644",
+ "index e69de29b..ff464d15 100644",
"--- a/null.js",
"+++ b/null.js",
"@@ -0,0 +1 @@",
"+null;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "655d7887b70794042aa3e0f4d6ea174c1b32af1c..f25bb82f823a669a0b6a9c19160ba03ab21d318b"
+ "shas": "da816fd1d09e1ffe56fc188b498a7f2312d7d0f2..e7d88f955c1b6a0f33229a754bc110dd810fc8ad"
}
,{
"testCaseDescription": "javascript-null-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/null.js b/null.js",
- "index ff464d1..2d3c3e0 100644",
+ "index ff464d15..2d3c3e03 100644",
"--- a/null.js",
"+++ b/null.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" null;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f25bb82f823a669a0b6a9c19160ba03ab21d318b..4669bb697216411b02390ac038c699f1db9d76ee"
+ "shas": "e7d88f955c1b6a0f33229a754bc110dd810fc8ad..c7f7e60754dec8e129b67699cd44585db218eece"
}
,{
"testCaseDescription": "javascript-null-delete-insert-test",
@@ -135,7 +135,7 @@
],
"patch": [
"diff --git a/null.js b/null.js",
- "index 2d3c3e0..3122897 100644",
+ "index 2d3c3e03..3122897c 100644",
"--- a/null.js",
"+++ b/null.js",
"@@ -1,3 +1,3 @@",
@@ -145,7 +145,7 @@
" null;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4669bb697216411b02390ac038c699f1db9d76ee..ff3a8cc7449b04b7a15a6ab31ea1f5e78283db3e"
+ "shas": "c7f7e60754dec8e129b67699cd44585db218eece..7a6700d2dd991b93c9f3f0c50edc6e3938217310"
}
,{
"testCaseDescription": "javascript-null-replacement-test",
@@ -191,7 +191,7 @@
],
"patch": [
"diff --git a/null.js b/null.js",
- "index 3122897..2d3c3e0 100644",
+ "index 3122897c..2d3c3e03 100644",
"--- a/null.js",
"+++ b/null.js",
"@@ -1,3 +1,3 @@",
@@ -201,7 +201,7 @@
" null;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ff3a8cc7449b04b7a15a6ab31ea1f5e78283db3e..0e96cfb0a6c4746ef4911d99134eebcac36edbd8"
+ "shas": "7a6700d2dd991b93c9f3f0c50edc6e3938217310..dd8895a31f17991ca681b4335900962830f53bbc"
}
,{
"testCaseDescription": "javascript-null-delete-replacement-test",
@@ -262,7 +262,7 @@
],
"patch": [
"diff --git a/null.js b/null.js",
- "index 2d3c3e0..0eb99c8 100644",
+ "index 2d3c3e03..0eb99c86 100644",
"--- a/null.js",
"+++ b/null.js",
"@@ -1,3 +1,2 @@",
@@ -272,7 +272,7 @@
"+return null;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0e96cfb0a6c4746ef4911d99134eebcac36edbd8..88958970d3cca5d0413e83a7ff37f1092d0d9299"
+ "shas": "dd8895a31f17991ca681b4335900962830f53bbc..699d55578394b6001c5993580ab915f359c8857e"
}
,{
"testCaseDescription": "javascript-null-delete-test",
@@ -303,7 +303,7 @@
],
"patch": [
"diff --git a/null.js b/null.js",
- "index 0eb99c8..76137ff 100644",
+ "index 0eb99c86..76137ff0 100644",
"--- a/null.js",
"+++ b/null.js",
"@@ -1,2 +1 @@",
@@ -311,7 +311,7 @@
" return null;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "88958970d3cca5d0413e83a7ff37f1092d0d9299..b5db27b021a3c11c985a28653aca15041f140fec"
+ "shas": "699d55578394b6001c5993580ab915f359c8857e..5630d055d7d52c192e8506561f1e126ce014c6eb"
}
,{
"testCaseDescription": "javascript-null-delete-rest-test",
@@ -342,12 +342,12 @@
],
"patch": [
"diff --git a/null.js b/null.js",
- "index 76137ff..e69de29 100644",
+ "index 76137ff0..e69de29b 100644",
"--- a/null.js",
"+++ b/null.js",
"@@ -1 +0,0 @@",
"-return null;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b5db27b021a3c11c985a28653aca15041f140fec..9f36bd70533d2f145bb9661791f0ea760bf949d5"
+ "shas": "5630d055d7d52c192e8506561f1e126ce014c6eb..2f535d692705ba01866febca83c7f3cb4af53987"
}]
diff --git a/test/corpus/diff-summaries/javascript/number.json b/test/corpus/diff-summaries/javascript/number.json
index 4e8d7ac06..bd1fc2127 100644
--- a/test/corpus/diff-summaries/javascript/number.json
+++ b/test/corpus/diff-summaries/javascript/number.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/number.js b/number.js",
- "index e69de29..398050c 100644",
+ "index e69de29b..398050c6 100644",
"--- a/number.js",
"+++ b/number.js",
"@@ -0,0 +1 @@",
"+101"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "aa6143f1a8ae9ca9b1ee3577121858208df3cce0..3838259f90e9c1e4e6ce33e99b8d9a0fbcd9e616"
+ "shas": "6973df063cce62bb3a038ea4124571d47a2c9083..e1ac9add54a38da5738a49903820e2a3f5db3f52"
}
,{
"testCaseDescription": "javascript-number-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/number.js b/number.js",
- "index 398050c..16da476 100644",
+ "index 398050c6..16da476c 100644",
"--- a/number.js",
"+++ b/number.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" 101"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3838259f90e9c1e4e6ce33e99b8d9a0fbcd9e616..6e18d86d44c74acdcea5dc6ea75a8169152e0dd2"
+ "shas": "e1ac9add54a38da5738a49903820e2a3f5db3f52..2445bb7656755d88141c3503580a987fada88d34"
}
,{
"testCaseDescription": "javascript-number-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/number.js b/number.js",
- "index 16da476..252b3e8 100644",
+ "index 16da476c..252b3e84 100644",
"--- a/number.js",
"+++ b/number.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" 101"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6e18d86d44c74acdcea5dc6ea75a8169152e0dd2..b40e32fd74e885cdf5d9617ef37150ec3d414177"
+ "shas": "2445bb7656755d88141c3503580a987fada88d34..a489f5fb28c2cc4be7b3d8015c0f5bebe43f060e"
}
,{
"testCaseDescription": "javascript-number-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/number.js b/number.js",
- "index 252b3e8..16da476 100644",
+ "index 252b3e84..16da476c 100644",
"--- a/number.js",
"+++ b/number.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" 101"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b40e32fd74e885cdf5d9617ef37150ec3d414177..85a591e8bebf6a7b8b9adfdebebfb4b8776ab809"
+ "shas": "a489f5fb28c2cc4be7b3d8015c0f5bebe43f060e..724c567757b9566241eee14f7b0bfa74b1bd2f09"
}
,{
"testCaseDescription": "javascript-number-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/number.js b/number.js",
- "index 16da476..bb77dfb 100644",
+ "index 16da476c..bb77dfbd 100644",
"--- a/number.js",
"+++ b/number.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+102"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "85a591e8bebf6a7b8b9adfdebebfb4b8776ab809..3e5ee4738617f0b4536cee654c79c7c71e8d7e7b"
+ "shas": "724c567757b9566241eee14f7b0bfa74b1bd2f09..c5684c3b9e9b42ff8b3eaac28d88f49bef71ffa9"
}
,{
"testCaseDescription": "javascript-number-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/number.js b/number.js",
- "index bb77dfb..257e563 100644",
+ "index bb77dfbd..257e5632 100644",
"--- a/number.js",
"+++ b/number.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" 102"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3e5ee4738617f0b4536cee654c79c7c71e8d7e7b..15bf3e42bb84c62933b0d29e0b675bca24cc66b2"
+ "shas": "c5684c3b9e9b42ff8b3eaac28d88f49bef71ffa9..747da5bd094aaa871b8ef06d65a18b02c0c74f9c"
}
,{
"testCaseDescription": "javascript-number-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/number.js b/number.js",
- "index 257e563..e69de29 100644",
+ "index 257e5632..e69de29b 100644",
"--- a/number.js",
"+++ b/number.js",
"@@ -1 +0,0 @@",
"-102"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "15bf3e42bb84c62933b0d29e0b675bca24cc66b2..2e348ee88f62c0857d6f6ce2ab3ee0d46f12afeb"
+ "shas": "747da5bd094aaa871b8ef06d65a18b02c0c74f9c..3ab54dc1f52a044020029364417b8c1e44102ef5"
}]
diff --git a/test/corpus/diff-summaries/javascript/object.json b/test/corpus/diff-summaries/javascript/object.json
index ad49fc815..6195d7447 100644
--- a/test/corpus/diff-summaries/javascript/object.json
+++ b/test/corpus/diff-summaries/javascript/object.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/object.js b/object.js",
- "index e69de29..fe17bb2 100644",
+ "index e69de29b..fe17bb20 100644",
"--- a/object.js",
"+++ b/object.js",
"@@ -0,0 +1 @@",
"+{ \"key1\": \"value1\" };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5dede241573c8e353a4d8c662194e8e3b750e01a..45f29912e03b7de277df4c10ad238121235b6ed7"
+ "shas": "80946fe6667b3843c0bd704136ac929ca5f2e3e0..f818678be5d0b2df6f23b3c92b836e869c9371df"
}
,{
"testCaseDescription": "javascript-object-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/object.js b/object.js",
- "index fe17bb2..741c3dc 100644",
+ "index fe17bb20..741c3dc1 100644",
"--- a/object.js",
"+++ b/object.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" { \"key1\": \"value1\" };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "45f29912e03b7de277df4c10ad238121235b6ed7..4e17781769a2098bcce839e1282b1fa0d1df7821"
+ "shas": "f818678be5d0b2df6f23b3c92b836e869c9371df..297febce60236ced0d896565c7d204e67f7d159c"
}
,{
"testCaseDescription": "javascript-object-delete-insert-test",
@@ -135,7 +135,7 @@
],
"patch": [
"diff --git a/object.js b/object.js",
- "index 741c3dc..701239d 100644",
+ "index 741c3dc1..701239d4 100644",
"--- a/object.js",
"+++ b/object.js",
"@@ -1,3 +1,3 @@",
@@ -145,7 +145,7 @@
" { \"key1\": \"value1\" };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4e17781769a2098bcce839e1282b1fa0d1df7821..d035734af1172dab5eb30ad01fe898f5d850606c"
+ "shas": "297febce60236ced0d896565c7d204e67f7d159c..32202a1cf37fa52d801a7a1b8df9dad201a6783c"
}
,{
"testCaseDescription": "javascript-object-replacement-test",
@@ -191,7 +191,7 @@
],
"patch": [
"diff --git a/object.js b/object.js",
- "index 701239d..741c3dc 100644",
+ "index 701239d4..741c3dc1 100644",
"--- a/object.js",
"+++ b/object.js",
"@@ -1,3 +1,3 @@",
@@ -201,7 +201,7 @@
" { \"key1\": \"value1\" };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d035734af1172dab5eb30ad01fe898f5d850606c..d172e093c2f663040bb8d2c429564a4d273753d3"
+ "shas": "32202a1cf37fa52d801a7a1b8df9dad201a6783c..d56a76751dbb5d10003fa22021a102affcc2c335"
}
,{
"testCaseDescription": "javascript-object-delete-replacement-test",
@@ -262,7 +262,7 @@
],
"patch": [
"diff --git a/object.js b/object.js",
- "index 741c3dc..9e48273 100644",
+ "index 741c3dc1..9e482739 100644",
"--- a/object.js",
"+++ b/object.js",
"@@ -1,3 +1,2 @@",
@@ -272,7 +272,7 @@
"+{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d172e093c2f663040bb8d2c429564a4d273753d3..337ff59260d3eed7762de977645c68224ea4d46c"
+ "shas": "d56a76751dbb5d10003fa22021a102affcc2c335..bbcaa8edd47182ad7eb2364f2896d42821d4f732"
}
,{
"testCaseDescription": "javascript-object-delete-test",
@@ -303,7 +303,7 @@
],
"patch": [
"diff --git a/object.js b/object.js",
- "index 9e48273..12d063a 100644",
+ "index 9e482739..12d063ad 100644",
"--- a/object.js",
"+++ b/object.js",
"@@ -1,2 +1 @@",
@@ -311,7 +311,7 @@
" { \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "337ff59260d3eed7762de977645c68224ea4d46c..9d30494c528991b340e861222f5a6276e874a964"
+ "shas": "bbcaa8edd47182ad7eb2364f2896d42821d4f732..65d9f0256a225ce371e57434daade7e2cb701429"
}
,{
"testCaseDescription": "javascript-object-delete-rest-test",
@@ -342,12 +342,12 @@
],
"patch": [
"diff --git a/object.js b/object.js",
- "index 12d063a..e69de29 100644",
+ "index 12d063ad..e69de29b 100644",
"--- a/object.js",
"+++ b/object.js",
"@@ -1 +0,0 @@",
"-{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9d30494c528991b340e861222f5a6276e874a964..ba01e3794a8efa31353fd2d5726c70bb2ad8c6a8"
+ "shas": "65d9f0256a225ce371e57434daade7e2cb701429..5bd86096402e987462d865b5963d5e68f31ef22d"
}]
diff --git a/test/corpus/diff-summaries/javascript/objects-with-methods.json b/test/corpus/diff-summaries/javascript/objects-with-methods.json
index 0ea47c67a..6686f4734 100644
--- a/test/corpus/diff-summaries/javascript/objects-with-methods.json
+++ b/test/corpus/diff-summaries/javascript/objects-with-methods.json
@@ -34,7 +34,7 @@
"+{ add(a, b) { return a + b; } };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5fe71a17cc99387501792a564bc50da57decd600..4851c63010b9106484a5f927916b5649e8e51dbd"
+ "shas": "aab57fb5b99b7d08c03849736ffa873c26495bec..8e3959c29f0fbb7c36d6460d98be17e83265684e"
}
,{
"testCaseDescription": "javascript-objects-with-methods-replacement-insert-test",
@@ -89,7 +89,7 @@
" { add(a, b) { return a + b; } };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4851c63010b9106484a5f927916b5649e8e51dbd..ff8a20b8f6098bb77aecc7af4cd21794488b4cda"
+ "shas": "8e3959c29f0fbb7c36d6460d98be17e83265684e..1dd7c4c953171bdaa60df1cc61d2774036a4a911"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-insert-test",
@@ -169,7 +169,7 @@
" { add(a, b) { return a + b; } };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ff8a20b8f6098bb77aecc7af4cd21794488b4cda..0eb6d26bdbee9a47efa74182c2dfb9fa3c677c0c"
+ "shas": "1dd7c4c953171bdaa60df1cc61d2774036a4a911..776d7f2bd3377d17e5952465b39a9c227213a052"
}
,{
"testCaseDescription": "javascript-objects-with-methods-replacement-test",
@@ -249,7 +249,7 @@
" { add(a, b) { return a + b; } };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0eb6d26bdbee9a47efa74182c2dfb9fa3c677c0c..d799c888cbd8b3a2c5fd918488bfdced8c37e3b4"
+ "shas": "776d7f2bd3377d17e5952465b39a9c227213a052..a4c25fd891972e50faec3f1797ba0d555d39405a"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-replacement-test",
@@ -320,7 +320,7 @@
"+{ subtract(a, b) { return a - b; } };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d799c888cbd8b3a2c5fd918488bfdced8c37e3b4..95338f9afb1060c14d4181bf7fd428d43a7b9f04"
+ "shas": "a4c25fd891972e50faec3f1797ba0d555d39405a..0af647ed5fbe8751e1a782fe86117a09c34201bd"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-test",
@@ -359,7 +359,7 @@
" { subtract(a, b) { return a - b; } };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "95338f9afb1060c14d4181bf7fd428d43a7b9f04..cc541912a1dea8dbd3e1f25ec14c9de7bc3ecb06"
+ "shas": "0af647ed5fbe8751e1a782fe86117a09c34201bd..0c60058b1d25e4aacde516a306f333741c9cccbe"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-rest-test",
@@ -397,5 +397,5 @@
"-{ subtract(a, b) { return a - b; } };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "cc541912a1dea8dbd3e1f25ec14c9de7bc3ecb06..07a785cb4f0cfa49a60fdfbbce7d8ecbfd2a820b"
+ "shas": "0c60058b1d25e4aacde516a306f333741c9cccbe..3c2e1bb6f33f4497e1151ea52af30ddcf6dcfcd7"
}]
diff --git a/test/corpus/diff-summaries/javascript/regex.json b/test/corpus/diff-summaries/javascript/regex.json
index d7c178a87..b6fdd492e 100644
--- a/test/corpus/diff-summaries/javascript/regex.json
+++ b/test/corpus/diff-summaries/javascript/regex.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/regex.js b/regex.js",
- "index e69de29..b381842 100644",
+ "index e69de29b..b3818424 100644",
"--- a/regex.js",
"+++ b/regex.js",
"@@ -0,0 +1 @@",
"+/one/g;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "734bede3c6c3771f011aa729a417011d310ec5cc..9dbffbb28707342ebcd361c29b0d670a271ddb04"
+ "shas": "821df9c41798fbc70ad5ca5a5795c00b2cedb79c..2db757877a7c19866710b3aee81a03666c41b5c4"
}
,{
"testCaseDescription": "javascript-regex-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/regex.js b/regex.js",
- "index b381842..6ed4b42 100644",
+ "index b3818424..6ed4b424 100644",
"--- a/regex.js",
"+++ b/regex.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" /one/g;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9dbffbb28707342ebcd361c29b0d670a271ddb04..f294c4a4aac8d0a945272edb200af0866b0d5a0f"
+ "shas": "2db757877a7c19866710b3aee81a03666c41b5c4..c30aee5ff6ef112d49a7192d70292859a7b7031c"
}
,{
"testCaseDescription": "javascript-regex-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/regex.js b/regex.js",
- "index 6ed4b42..abb87ec 100644",
+ "index 6ed4b424..abb87ec8 100644",
"--- a/regex.js",
"+++ b/regex.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" /one/g;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f294c4a4aac8d0a945272edb200af0866b0d5a0f..c158c5219c063572ee6664525f8fb4377178cdc3"
+ "shas": "c30aee5ff6ef112d49a7192d70292859a7b7031c..5f611ea9f0400d0a16e8f26ed6bb0e77b9f182d4"
}
,{
"testCaseDescription": "javascript-regex-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/regex.js b/regex.js",
- "index abb87ec..6ed4b42 100644",
+ "index abb87ec8..6ed4b424 100644",
"--- a/regex.js",
"+++ b/regex.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" /one/g;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c158c5219c063572ee6664525f8fb4377178cdc3..38ad972ed8f499cb320e4584c4ae1b95d4e70f41"
+ "shas": "5f611ea9f0400d0a16e8f26ed6bb0e77b9f182d4..522e77adc0cf490332af21396f7b8fc1dadc1e0e"
}
,{
"testCaseDescription": "javascript-regex-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/regex.js b/regex.js",
- "index 6ed4b42..9f57e91 100644",
+ "index 6ed4b424..9f57e919 100644",
"--- a/regex.js",
"+++ b/regex.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+/on[^/]afe/gim;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "38ad972ed8f499cb320e4584c4ae1b95d4e70f41..79078d16f7a00fca2b3dbf3cf7dadd8f5ba7929c"
+ "shas": "522e77adc0cf490332af21396f7b8fc1dadc1e0e..3756349ee3c2a57533b0586b3efe8330bd649e1a"
}
,{
"testCaseDescription": "javascript-regex-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/regex.js b/regex.js",
- "index 9f57e91..9b04194 100644",
+ "index 9f57e919..9b04194d 100644",
"--- a/regex.js",
"+++ b/regex.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" /on[^/]afe/gim;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "79078d16f7a00fca2b3dbf3cf7dadd8f5ba7929c..f293398786080c6f5b99e7c36ba482702f5cbbae"
+ "shas": "3756349ee3c2a57533b0586b3efe8330bd649e1a..82af6ebb2352e85a6f3d0f5386f6685c24472554"
}
,{
"testCaseDescription": "javascript-regex-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/regex.js b/regex.js",
- "index 9b04194..e69de29 100644",
+ "index 9b04194d..e69de29b 100644",
"--- a/regex.js",
"+++ b/regex.js",
"@@ -1 +0,0 @@",
"-/on[^/]afe/gim;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f293398786080c6f5b99e7c36ba482702f5cbbae..4951403c16600a8ebe50779236bcbc480c823807"
+ "shas": "82af6ebb2352e85a6f3d0f5386f6685c24472554..2440322c22f20e4b94216aa19cb2249a68864183"
}]
diff --git a/test/corpus/diff-summaries/javascript/relational-operator.json b/test/corpus/diff-summaries/javascript/relational-operator.json
index 5a06be00e..0bab09513 100644
--- a/test/corpus/diff-summaries/javascript/relational-operator.json
+++ b/test/corpus/diff-summaries/javascript/relational-operator.json
@@ -34,7 +34,7 @@
"+x < y;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "1d234a84ee270c0d6a329fcdcbc065e50bed813b..f7081b58f603918674558efe269d8dbd1ffc0835"
+ "shas": "46ec065b158574c8c24c03f95bd0b21ae4388b86..2ee804aaa1d1aa4ef1be264a594321f6c02a1541"
}
,{
"testCaseDescription": "javascript-relational-operator-replacement-insert-test",
@@ -89,7 +89,7 @@
" x < y;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f7081b58f603918674558efe269d8dbd1ffc0835..57f5399d4cf2022a779be84e5e9ffe8f15beca07"
+ "shas": "2ee804aaa1d1aa4ef1be264a594321f6c02a1541..d1e56066308b5fc811554611927cac04e9eb93a6"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-insert-test",
@@ -142,7 +142,7 @@
" x < y;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "57f5399d4cf2022a779be84e5e9ffe8f15beca07..3161974cca9b971b21e69bbe11c32ece0e43e408"
+ "shas": "d1e56066308b5fc811554611927cac04e9eb93a6..ae6ce44b0acbdaf22a8f8f0d28b327b39ef0fb73"
}
,{
"testCaseDescription": "javascript-relational-operator-replacement-test",
@@ -195,7 +195,7 @@
" x < y;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3161974cca9b971b21e69bbe11c32ece0e43e408..b7a5454b7132955133e3749565ef37567cfa2d5e"
+ "shas": "ae6ce44b0acbdaf22a8f8f0d28b327b39ef0fb73..e84e3a360d79e551b0b12f9e863aaf9ac14067b9"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-replacement-test",
@@ -266,7 +266,7 @@
"+x <= y;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b7a5454b7132955133e3749565ef37567cfa2d5e..c40fd681cdd3b75acaf0826df149b0e9c13ceb4f"
+ "shas": "e84e3a360d79e551b0b12f9e863aaf9ac14067b9..f02fb7a346f03e6fc28dc2e5131f9e4e9b1f298e"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-test",
@@ -305,7 +305,7 @@
" x <= y;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c40fd681cdd3b75acaf0826df149b0e9c13ceb4f..7e0cd5e7ebf2702d445a75bb632353547258d65b"
+ "shas": "f02fb7a346f03e6fc28dc2e5131f9e4e9b1f298e..0bc1b2520e0ade68a9afef35280ef6928d45ac49"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-rest-test",
@@ -343,5 +343,5 @@
"-x <= y;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7e0cd5e7ebf2702d445a75bb632353547258d65b..8a27197df5dd32970d666dec2ed87840381ee268"
+ "shas": "0bc1b2520e0ade68a9afef35280ef6928d45ac49..e2f5e2a31d37bfe30697e216363db3575aa06a6a"
}]
diff --git a/test/corpus/diff-summaries/javascript/return-statement.json b/test/corpus/diff-summaries/javascript/return-statement.json
index a7ffcab5c..962237412 100644
--- a/test/corpus/diff-summaries/javascript/return-statement.json
+++ b/test/corpus/diff-summaries/javascript/return-statement.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/return-statement.js b/return-statement.js",
- "index e69de29..6315029 100644",
+ "index e69de29b..63150293 100644",
"--- a/return-statement.js",
"+++ b/return-statement.js",
"@@ -0,0 +1 @@",
"+return 5;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2795ba48a13af4b2c6f240761fd880dc6cd10c2b..65e3958e72f9b522fb419169e1dc79619e10fb0e"
+ "shas": "cfb33c769bbc24766b17e262f1c1eb05b0face8f..0aa153a74399560d168cd2de8143750bc9d2b7f4"
}
,{
"testCaseDescription": "javascript-return-statement-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/return-statement.js b/return-statement.js",
- "index 6315029..22dde95 100644",
+ "index 63150293..22dde951 100644",
"--- a/return-statement.js",
"+++ b/return-statement.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" return 5;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "65e3958e72f9b522fb419169e1dc79619e10fb0e..908a90ee504807c1ddcb0e7484d59bb97281136b"
+ "shas": "0aa153a74399560d168cd2de8143750bc9d2b7f4..0bc4edeb490e8a26916cdea48411d59a2dcbe9ea"
}
,{
"testCaseDescription": "javascript-return-statement-delete-insert-test",
@@ -120,7 +120,7 @@
],
"patch": [
"diff --git a/return-statement.js b/return-statement.js",
- "index 22dde95..522349c 100644",
+ "index 22dde951..522349cd 100644",
"--- a/return-statement.js",
"+++ b/return-statement.js",
"@@ -1,3 +1,3 @@",
@@ -130,7 +130,7 @@
" return 5;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "908a90ee504807c1ddcb0e7484d59bb97281136b..20240a05b2905df70c1ee93e3e6b9c931f2959cf"
+ "shas": "0bc4edeb490e8a26916cdea48411d59a2dcbe9ea..fbebc9a0fc19ad18e07eae7056ffc87f55c723ae"
}
,{
"testCaseDescription": "javascript-return-statement-replacement-test",
@@ -161,7 +161,7 @@
],
"patch": [
"diff --git a/return-statement.js b/return-statement.js",
- "index 522349c..22dde95 100644",
+ "index 522349cd..22dde951 100644",
"--- a/return-statement.js",
"+++ b/return-statement.js",
"@@ -1,3 +1,3 @@",
@@ -171,7 +171,7 @@
" return 5;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "20240a05b2905df70c1ee93e3e6b9c931f2959cf..13392621e30661ca237d268f3ef50e3c7012ae05"
+ "shas": "fbebc9a0fc19ad18e07eae7056ffc87f55c723ae..c6d4228f0de495dc97232ad34fbb898106b26588"
}
,{
"testCaseDescription": "javascript-return-statement-delete-replacement-test",
@@ -232,7 +232,7 @@
],
"patch": [
"diff --git a/return-statement.js b/return-statement.js",
- "index 22dde95..4d44d6a 100644",
+ "index 22dde951..4d44d6ac 100644",
"--- a/return-statement.js",
"+++ b/return-statement.js",
"@@ -1,3 +1,2 @@",
@@ -242,7 +242,7 @@
"+return;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "13392621e30661ca237d268f3ef50e3c7012ae05..fba0fb892c46997d3c955a13380af9805300ca83"
+ "shas": "c6d4228f0de495dc97232ad34fbb898106b26588..1083a5e11717877aa91a52745bf70643c0cf0e09"
}
,{
"testCaseDescription": "javascript-return-statement-delete-test",
@@ -273,7 +273,7 @@
],
"patch": [
"diff --git a/return-statement.js b/return-statement.js",
- "index 4d44d6a..f312410 100644",
+ "index 4d44d6ac..f312410b 100644",
"--- a/return-statement.js",
"+++ b/return-statement.js",
"@@ -1,2 +1 @@",
@@ -281,7 +281,7 @@
" return;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "fba0fb892c46997d3c955a13380af9805300ca83..81f231c35cf307c855a8fead87315cb8828c2371"
+ "shas": "1083a5e11717877aa91a52745bf70643c0cf0e09..08812679efc223693ed79c510e94be4370547f06"
}
,{
"testCaseDescription": "javascript-return-statement-delete-rest-test",
@@ -312,12 +312,12 @@
],
"patch": [
"diff --git a/return-statement.js b/return-statement.js",
- "index f312410..e69de29 100644",
+ "index f312410b..e69de29b 100644",
"--- a/return-statement.js",
"+++ b/return-statement.js",
"@@ -1 +0,0 @@",
"-return;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "81f231c35cf307c855a8fead87315cb8828c2371..5d2db352ed0e33bb51a7f2330066274984490127"
+ "shas": "08812679efc223693ed79c510e94be4370547f06..c90fef2277e371c606b2a159aee629c8a43edec2"
}]
diff --git a/test/corpus/diff-summaries/javascript/string.json b/test/corpus/diff-summaries/javascript/string.json
index f874ef732..46e52be24 100644
--- a/test/corpus/diff-summaries/javascript/string.json
+++ b/test/corpus/diff-summaries/javascript/string.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/string.js b/string.js",
- "index e69de29..ea5bd42 100644",
+ "index e69de29b..ea5bd425 100644",
"--- a/string.js",
"+++ b/string.js",
"@@ -0,0 +1 @@",
"+'A string with \"double\" quotes';"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c1ec2fd690eae01418882f3dbba8b6a5c0c3c2eb..dd9d769102a7c17e08e27bae6e4e070a6677cd7f"
+ "shas": "3c2e1bb6f33f4497e1151ea52af30ddcf6dcfcd7..3ba34eb51aaf7a4ba4049b784c63092efcfe86ec"
}
,{
"testCaseDescription": "javascript-string-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/string.js b/string.js",
- "index ea5bd42..5cef047 100644",
+ "index ea5bd425..5cef047e 100644",
"--- a/string.js",
"+++ b/string.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" 'A string with \"double\" quotes';"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "dd9d769102a7c17e08e27bae6e4e070a6677cd7f..6504adbbbbdb0f45a0fba583ccb72ff50cdf8349"
+ "shas": "3ba34eb51aaf7a4ba4049b784c63092efcfe86ec..cc71e24b9defde56a3163b06e53add09e5ef3e4d"
}
,{
"testCaseDescription": "javascript-string-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/string.js b/string.js",
- "index 5cef047..7af39a5 100644",
+ "index 5cef047e..7af39a55 100644",
"--- a/string.js",
"+++ b/string.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" 'A string with \"double\" quotes';"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6504adbbbbdb0f45a0fba583ccb72ff50cdf8349..d39f387280812bce0247667978d542ebe0d27bcb"
+ "shas": "cc71e24b9defde56a3163b06e53add09e5ef3e4d..3322d99a7ccfef32ba3dd025b13d2fb041746404"
}
,{
"testCaseDescription": "javascript-string-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/string.js b/string.js",
- "index 7af39a5..5cef047 100644",
+ "index 7af39a55..5cef047e 100644",
"--- a/string.js",
"+++ b/string.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" 'A string with \"double\" quotes';"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d39f387280812bce0247667978d542ebe0d27bcb..b2f472510952cefbc5514307177170e71e3599ec"
+ "shas": "3322d99a7ccfef32ba3dd025b13d2fb041746404..befbd0d4f556ba947b8b22393ac13ac8d67d9e82"
}
,{
"testCaseDescription": "javascript-string-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/string.js b/string.js",
- "index 5cef047..8dd4514 100644",
+ "index 5cef047e..8dd4514f 100644",
"--- a/string.js",
"+++ b/string.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+'A different string with \"double\" quotes';"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b2f472510952cefbc5514307177170e71e3599ec..e83edaaa1afe0823f876025cf3b281bf6f6ab951"
+ "shas": "befbd0d4f556ba947b8b22393ac13ac8d67d9e82..08b5dc1f18c4153bae2f92a163bf79352942ffef"
}
,{
"testCaseDescription": "javascript-string-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/string.js b/string.js",
- "index 8dd4514..95fbde5 100644",
+ "index 8dd4514f..95fbde5d 100644",
"--- a/string.js",
"+++ b/string.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" 'A different string with \"double\" quotes';"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "e83edaaa1afe0823f876025cf3b281bf6f6ab951..b00ba4fad86fcb97c8703641c255c5ca427424eb"
+ "shas": "08b5dc1f18c4153bae2f92a163bf79352942ffef..8f2189894058b7aabe2f63349a1dc7a2326f5a1c"
}
,{
"testCaseDescription": "javascript-string-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/string.js b/string.js",
- "index 95fbde5..e69de29 100644",
+ "index 95fbde5d..e69de29b 100644",
"--- a/string.js",
"+++ b/string.js",
"@@ -1 +0,0 @@",
"-'A different string with \"double\" quotes';"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b00ba4fad86fcb97c8703641c255c5ca427424eb..aa6143f1a8ae9ca9b1ee3577121858208df3cce0"
+ "shas": "8f2189894058b7aabe2f63349a1dc7a2326f5a1c..6973df063cce62bb3a038ea4124571d47a2c9083"
}]
diff --git a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json
index b334fc8c8..6a0054810 100644
--- a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json
+++ b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
- "index e69de29..6b6d48d 100644",
+ "index e69de29b..6b6d48d2 100644",
"--- a/subscript-access-assignment.js",
"+++ b/subscript-access-assignment.js",
"@@ -0,0 +1 @@",
"+y[\"x\"] = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "faf582893e706ae259a0482d65d424fbcf137bb2..b59647bbb7592da11c7d4ac78458e63e854b04f3"
+ "shas": "4771589971576b44762a611a7b4b4cbdb9259735..0cfddba7d07880a41ca2de997a9a905ca8395b86"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
- "index 6b6d48d..17d3ff4 100644",
+ "index 6b6d48d2..17d3ff48 100644",
"--- a/subscript-access-assignment.js",
"+++ b/subscript-access-assignment.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" y[\"x\"] = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b59647bbb7592da11c7d4ac78458e63e854b04f3..8b0173919309e1b0e73ab4a4a4fcd8dd02bc0ccb"
+ "shas": "0cfddba7d07880a41ca2de997a9a905ca8395b86..c4524a646dc110253088196709418c9c7973b24e"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
- "index 17d3ff4..d856ac0 100644",
+ "index 17d3ff48..d856ac0d 100644",
"--- a/subscript-access-assignment.js",
"+++ b/subscript-access-assignment.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" y[\"x\"] = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8b0173919309e1b0e73ab4a4a4fcd8dd02bc0ccb..461eebed467430133c1996ed21dd6e72dd4f06ac"
+ "shas": "c4524a646dc110253088196709418c9c7973b24e..5441e85813c5d2a2a412609c15592022ecac4471"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
- "index d856ac0..17d3ff4 100644",
+ "index d856ac0d..17d3ff48 100644",
"--- a/subscript-access-assignment.js",
"+++ b/subscript-access-assignment.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" y[\"x\"] = 0;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "461eebed467430133c1996ed21dd6e72dd4f06ac..689acd0e8c575ae20e8d6acaa4522119800c3a39"
+ "shas": "5441e85813c5d2a2a412609c15592022ecac4471..75a07bef0582ba59d8b878d49058c73cba104455"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
- "index 17d3ff4..cdcb426 100644",
+ "index 17d3ff48..cdcb426e 100644",
"--- a/subscript-access-assignment.js",
"+++ b/subscript-access-assignment.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+y[\"x\"] = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "689acd0e8c575ae20e8d6acaa4522119800c3a39..a124eee21e5e3f952e498fb2175d1497ca06aa13"
+ "shas": "75a07bef0582ba59d8b878d49058c73cba104455..921de36fbbb7fea44d2d5910e8b6a58e9866f8c3"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
- "index cdcb426..0407c3a 100644",
+ "index cdcb426e..0407c3a1 100644",
"--- a/subscript-access-assignment.js",
"+++ b/subscript-access-assignment.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" y[\"x\"] = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "a124eee21e5e3f952e498fb2175d1497ca06aa13..194ef1fb19bf18a70a7e1a0dd198c832d2383bd9"
+ "shas": "921de36fbbb7fea44d2d5910e8b6a58e9866f8c3..bf26a76e4e4ccc3b3705ef27a866546586322ea3"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/subscript-access-assignment.js b/subscript-access-assignment.js",
- "index 0407c3a..e69de29 100644",
+ "index 0407c3a1..e69de29b 100644",
"--- a/subscript-access-assignment.js",
"+++ b/subscript-access-assignment.js",
"@@ -1 +0,0 @@",
"-y[\"x\"] = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "194ef1fb19bf18a70a7e1a0dd198c832d2383bd9..ec86aaba01801d01aca70fd31403642be1e2d438"
+ "shas": "bf26a76e4e4ccc3b3705ef27a866546586322ea3..a51b44e93b10645f205b119e37a93f384ee4d64c"
}]
diff --git a/test/corpus/diff-summaries/javascript/subscript-access-string.json b/test/corpus/diff-summaries/javascript/subscript-access-string.json
index 13e2db731..6e231ee88 100644
--- a/test/corpus/diff-summaries/javascript/subscript-access-string.json
+++ b/test/corpus/diff-summaries/javascript/subscript-access-string.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/subscript-access-string.js b/subscript-access-string.js",
- "index e69de29..4293717 100644",
+ "index e69de29b..42937172 100644",
"--- a/subscript-access-string.js",
"+++ b/subscript-access-string.js",
"@@ -0,0 +1 @@",
"+x[\"some-string\"];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b6fd9fdbec2e79ee92f6829605a2e1a54a1784ba..bf933db8b20ff7bc2d86eb5a8e8082fd78234e87"
+ "shas": "595d5ea7f9ffe79492570e798289e541318c0040..fc2933a8010b3e7f410a66fc55bad738b6284c95"
}
,{
"testCaseDescription": "javascript-subscript-access-string-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/subscript-access-string.js b/subscript-access-string.js",
- "index 4293717..4293009 100644",
+ "index 42937172..42930094 100644",
"--- a/subscript-access-string.js",
"+++ b/subscript-access-string.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" x[\"some-string\"];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "bf933db8b20ff7bc2d86eb5a8e8082fd78234e87..3cc4eb9c46cd85ade63c176295763ab093268536"
+ "shas": "fc2933a8010b3e7f410a66fc55bad738b6284c95..57e6a5667b38fa4c3c7ab33b4694165dd2c4ed84"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/subscript-access-string.js b/subscript-access-string.js",
- "index 4293009..c53d07b 100644",
+ "index 42930094..c53d07bb 100644",
"--- a/subscript-access-string.js",
"+++ b/subscript-access-string.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" x[\"some-string\"];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3cc4eb9c46cd85ade63c176295763ab093268536..182d9efc50b49dfedd82b47b3382606f3bd57567"
+ "shas": "57e6a5667b38fa4c3c7ab33b4694165dd2c4ed84..19f6ce0423899b55e673f1dc7e60940270d8ad8f"
}
,{
"testCaseDescription": "javascript-subscript-access-string-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/subscript-access-string.js b/subscript-access-string.js",
- "index c53d07b..4293009 100644",
+ "index c53d07bb..42930094 100644",
"--- a/subscript-access-string.js",
"+++ b/subscript-access-string.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" x[\"some-string\"];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "182d9efc50b49dfedd82b47b3382606f3bd57567..203a1ff0e0cd35b08ded73803e92f3094a9a0bd7"
+ "shas": "19f6ce0423899b55e673f1dc7e60940270d8ad8f..dfd81c6a4d943edd07acaa9d48a6519c80a06050"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/subscript-access-string.js b/subscript-access-string.js",
- "index 4293009..89c1bc2 100644",
+ "index 42930094..89c1bc26 100644",
"--- a/subscript-access-string.js",
"+++ b/subscript-access-string.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+x[\"some-other-string\"];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "203a1ff0e0cd35b08ded73803e92f3094a9a0bd7..d4061981099d5b4d806f6786addfa3faba8b1dfe"
+ "shas": "dfd81c6a4d943edd07acaa9d48a6519c80a06050..0dfb6401873b87137de6fdd942f470475d246b0c"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/subscript-access-string.js b/subscript-access-string.js",
- "index 89c1bc2..758f8e7 100644",
+ "index 89c1bc26..758f8e70 100644",
"--- a/subscript-access-string.js",
"+++ b/subscript-access-string.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" x[\"some-other-string\"];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d4061981099d5b4d806f6786addfa3faba8b1dfe..0b3a01d8665ee9e2126b68009c7a8c9d41fca3c8"
+ "shas": "0dfb6401873b87137de6fdd942f470475d246b0c..fa446147a3c9218f0d62f0d07f3b3bf26787b8f5"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/subscript-access-string.js b/subscript-access-string.js",
- "index 758f8e7..e69de29 100644",
+ "index 758f8e70..e69de29b 100644",
"--- a/subscript-access-string.js",
"+++ b/subscript-access-string.js",
"@@ -1 +0,0 @@",
"-x[\"some-other-string\"];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0b3a01d8665ee9e2126b68009c7a8c9d41fca3c8..71feda9fd80ab60adab5cf81748710b2a610173f"
+ "shas": "fa446147a3c9218f0d62f0d07f3b3bf26787b8f5..c0d1f59dbc88b8a161e9dfa867107276f10b2898"
}]
diff --git a/test/corpus/diff-summaries/javascript/subscript-access-variable.json b/test/corpus/diff-summaries/javascript/subscript-access-variable.json
index 5e7e265f2..43b98a8b8 100644
--- a/test/corpus/diff-summaries/javascript/subscript-access-variable.json
+++ b/test/corpus/diff-summaries/javascript/subscript-access-variable.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
- "index e69de29..9a7b3d3 100644",
+ "index e69de29b..9a7b3d3e 100644",
"--- a/subscript-access-variable.js",
"+++ b/subscript-access-variable.js",
"@@ -0,0 +1 @@",
"+x[someVariable];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "bcba202e709aea072f614c126e2a5bb356cbf3fe..f506206202b7ba25d0d7002482361368d4484792"
+ "shas": "9043f23503e9e2afefc8849bfc0831696797e235..7d3ca01ea8bfa2f99dd7dcac2d37e21f3bd3bcb5"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
- "index 9a7b3d3..000d190 100644",
+ "index 9a7b3d3e..000d190c 100644",
"--- a/subscript-access-variable.js",
"+++ b/subscript-access-variable.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" x[someVariable];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f506206202b7ba25d0d7002482361368d4484792..bc70d1984738705b4df815056d104a56f917365b"
+ "shas": "7d3ca01ea8bfa2f99dd7dcac2d37e21f3bd3bcb5..47622b188e3f9eafb71931192d7f7f5ff4c6b75d"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
- "index 000d190..01f61ef 100644",
+ "index 000d190c..01f61ef9 100644",
"--- a/subscript-access-variable.js",
"+++ b/subscript-access-variable.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" x[someVariable];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "bc70d1984738705b4df815056d104a56f917365b..912cf4a3c64ca194b5497e5fd9730ea2311d3947"
+ "shas": "47622b188e3f9eafb71931192d7f7f5ff4c6b75d..4e3a569646ad726efdedd049312ff80c603e2ebd"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
- "index 01f61ef..000d190 100644",
+ "index 01f61ef9..000d190c 100644",
"--- a/subscript-access-variable.js",
"+++ b/subscript-access-variable.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" x[someVariable];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "912cf4a3c64ca194b5497e5fd9730ea2311d3947..2b501586eba02bbd8e3ea2313ae892d24672a95d"
+ "shas": "4e3a569646ad726efdedd049312ff80c603e2ebd..a46c2acd3e4d2e45fe3fc19674598f6ee9e65cf1"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
- "index 000d190..2aaae7e 100644",
+ "index 000d190c..2aaae7e7 100644",
"--- a/subscript-access-variable.js",
"+++ b/subscript-access-variable.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+x[someOtherVariable];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2b501586eba02bbd8e3ea2313ae892d24672a95d..188b43fc4ab2de0e499492f21c5b24308c26e908"
+ "shas": "a46c2acd3e4d2e45fe3fc19674598f6ee9e65cf1..e0b0772d0b873472a0c13bcaf10d73a1f1825d2f"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
- "index 2aaae7e..baa3661 100644",
+ "index 2aaae7e7..baa3661b 100644",
"--- a/subscript-access-variable.js",
"+++ b/subscript-access-variable.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" x[someOtherVariable];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "188b43fc4ab2de0e499492f21c5b24308c26e908..386de21b188a783b6a0a9b5c024f0c92082dbfde"
+ "shas": "e0b0772d0b873472a0c13bcaf10d73a1f1825d2f..a2281c261cd387de9408287b0085055c1afd3640"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/subscript-access-variable.js b/subscript-access-variable.js",
- "index baa3661..e69de29 100644",
+ "index baa3661b..e69de29b 100644",
"--- a/subscript-access-variable.js",
"+++ b/subscript-access-variable.js",
"@@ -1 +0,0 @@",
"-x[someOtherVariable];"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "386de21b188a783b6a0a9b5c024f0c92082dbfde..b6fd9fdbec2e79ee92f6829605a2e1a54a1784ba"
+ "shas": "a2281c261cd387de9408287b0085055c1afd3640..595d5ea7f9ffe79492570e798289e541318c0040"
}]
diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json
index 772831666..153d06b83 100644
--- a/test/corpus/diff-summaries/javascript/switch-statement.json
+++ b/test/corpus/diff-summaries/javascript/switch-statement.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/switch-statement.js b/switch-statement.js",
- "index e69de29..5481c49 100644",
+ "index e69de29b..5481c49f 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",
- "shas": "8f7edd21ecef61769b82fb5a60a881f31ce30a01..9e6646e9f984497bc80a1c1f1afb86eb869c9b26"
+ "shas": "20109cf62d65353fadfe9965edbf1f9e875db9c4..41b828f4af89e6677a4997fe9d4b9cc8ad5a8268"
}
,{
"testCaseDescription": "javascript-switch-statement-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/switch-statement.js b/switch-statement.js",
- "index 5481c49..ffd4a32 100644",
+ "index 5481c49f..ffd4a32a 100644",
"--- a/switch-statement.js",
"+++ b/switch-statement.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" switch (1) { case 1: 1; case 2: 1; case 3: 3; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9e6646e9f984497bc80a1c1f1afb86eb869c9b26..887d9088c295dc7a59711a02769e0754c6d1fa33"
+ "shas": "41b828f4af89e6677a4997fe9d4b9cc8ad5a8268..b21a69cfb5bddfed6b44656554b88ba169752dcf"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-insert-test",
@@ -159,7 +159,7 @@
],
"patch": [
"diff --git a/switch-statement.js b/switch-statement.js",
- "index ffd4a32..302fb8b 100644",
+ "index ffd4a32a..302fb8bc 100644",
"--- a/switch-statement.js",
"+++ b/switch-statement.js",
"@@ -1,3 +1,3 @@",
@@ -169,7 +169,7 @@
" switch (1) { case 1: 1; case 2: 1; case 3: 3; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "887d9088c295dc7a59711a02769e0754c6d1fa33..ba0bf7fe9de15a5f734f4e4c6059ce15c34e8311"
+ "shas": "b21a69cfb5bddfed6b44656554b88ba169752dcf..7c2c88ac6ae82fe4371fefaeaf5f839395d35fa4"
}
,{
"testCaseDescription": "javascript-switch-statement-replacement-test",
@@ -239,7 +239,7 @@
],
"patch": [
"diff --git a/switch-statement.js b/switch-statement.js",
- "index 302fb8b..ffd4a32 100644",
+ "index 302fb8bc..ffd4a32a 100644",
"--- a/switch-statement.js",
"+++ b/switch-statement.js",
"@@ -1,3 +1,3 @@",
@@ -249,7 +249,7 @@
" switch (1) { case 1: 1; case 2: 1; case 3: 3; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ba0bf7fe9de15a5f734f4e4c6059ce15c34e8311..213e3cb9828fdcbfe60dea518fb77b1896af15bb"
+ "shas": "7c2c88ac6ae82fe4371fefaeaf5f839395d35fa4..8c80e040d635672848180ef8fe6acefbf8c93fbc"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-replacement-test",
@@ -310,7 +310,7 @@
],
"patch": [
"diff --git a/switch-statement.js b/switch-statement.js",
- "index ffd4a32..9b60579 100644",
+ "index ffd4a32a..9b605791 100644",
"--- a/switch-statement.js",
"+++ b/switch-statement.js",
"@@ -1,3 +1,2 @@",
@@ -320,7 +320,7 @@
"+switch (2) { case 1: 1; case 2: 2; case 3: 3; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "213e3cb9828fdcbfe60dea518fb77b1896af15bb..a818910ed9354ea4b6070e11af8de9cefd66aedf"
+ "shas": "8c80e040d635672848180ef8fe6acefbf8c93fbc..bd3aa8f2fcea05110e0b7efb3d7662b3de7bf631"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-test",
@@ -351,7 +351,7 @@
],
"patch": [
"diff --git a/switch-statement.js b/switch-statement.js",
- "index 9b60579..374091f 100644",
+ "index 9b605791..374091f2 100644",
"--- a/switch-statement.js",
"+++ b/switch-statement.js",
"@@ -1,2 +1 @@",
@@ -359,7 +359,7 @@
" switch (2) { case 1: 1; case 2: 2; case 3: 3; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "a818910ed9354ea4b6070e11af8de9cefd66aedf..db5abd71dd4f34b20163d37657b839707b279e09"
+ "shas": "bd3aa8f2fcea05110e0b7efb3d7662b3de7bf631..70d56762d3e6f27e10409d458adfa25226b79a99"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-rest-test",
@@ -390,12 +390,12 @@
],
"patch": [
"diff --git a/switch-statement.js b/switch-statement.js",
- "index 374091f..e69de29 100644",
+ "index 374091f2..e69de29b 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",
- "shas": "db5abd71dd4f34b20163d37657b839707b279e09..8e3f45940f773e7849a53fefdaeb52a682a6a488"
+ "shas": "70d56762d3e6f27e10409d458adfa25226b79a99..20c612d09dbfc0c2c4ab61b7c9234d17faa3f43e"
}]
diff --git a/test/corpus/diff-summaries/javascript/template-string.json b/test/corpus/diff-summaries/javascript/template-string.json
index 0e00c7bd5..16684bedc 100644
--- a/test/corpus/diff-summaries/javascript/template-string.json
+++ b/test/corpus/diff-summaries/javascript/template-string.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/template-string.js b/template-string.js",
- "index e69de29..01f859b 100644",
+ "index e69de29b..01f859b1 100644",
"--- a/template-string.js",
"+++ b/template-string.js",
"@@ -0,0 +1 @@",
"+`one line`"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "dffe792710a5ad52de12ed62e48340a71e5c9227..4f86472b03fd24538a67565981a8d25700240497"
+ "shas": "b0cccfc42d36aba8e42003998233c798245c627f..2040236e0fd466e286462380a49b72595d79d6a9"
}
,{
"testCaseDescription": "javascript-template-string-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/template-string.js b/template-string.js",
- "index 01f859b..777fde6 100644",
+ "index 01f859b1..777fde68 100644",
"--- a/template-string.js",
"+++ b/template-string.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" `one line`"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4f86472b03fd24538a67565981a8d25700240497..8e2e8be8c6d60e68e5851f727da2c71ace094f34"
+ "shas": "2040236e0fd466e286462380a49b72595d79d6a9..05f27649aa9bc187d1ebfcc9810842f8992e3fd7"
}
,{
"testCaseDescription": "javascript-template-string-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/template-string.js b/template-string.js",
- "index 777fde6..657129f 100644",
+ "index 777fde68..657129fc 100644",
"--- a/template-string.js",
"+++ b/template-string.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" `one line`"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8e2e8be8c6d60e68e5851f727da2c71ace094f34..a481b18c353836ec0291fd6a2e9ea424de6b7a8c"
+ "shas": "05f27649aa9bc187d1ebfcc9810842f8992e3fd7..aa5a50db04e0712c494739ab35e56368a5a3f498"
}
,{
"testCaseDescription": "javascript-template-string-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/template-string.js b/template-string.js",
- "index 657129f..777fde6 100644",
+ "index 657129fc..777fde68 100644",
"--- a/template-string.js",
"+++ b/template-string.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" `one line`"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "a481b18c353836ec0291fd6a2e9ea424de6b7a8c..671ff7c523a3b938440bc9534540d94f391acd9e"
+ "shas": "aa5a50db04e0712c494739ab35e56368a5a3f498..b81a678bbbb5ef57d6c873d1fa629c0c23463dda"
}
,{
"testCaseDescription": "javascript-template-string-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/template-string.js b/template-string.js",
- "index 777fde6..2b8c0dd 100644",
+ "index 777fde68..2b8c0dde 100644",
"--- a/template-string.js",
"+++ b/template-string.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+`multi line`"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "671ff7c523a3b938440bc9534540d94f391acd9e..ba89b5cfbffb97d143c19125b8ed8e468113cd32"
+ "shas": "b81a678bbbb5ef57d6c873d1fa629c0c23463dda..f70c47ebd50d4c6a193f45e79414ba29cb16e719"
}
,{
"testCaseDescription": "javascript-template-string-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/template-string.js b/template-string.js",
- "index 2b8c0dd..399f117 100644",
+ "index 2b8c0dde..399f1173 100644",
"--- a/template-string.js",
"+++ b/template-string.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" `multi line`"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ba89b5cfbffb97d143c19125b8ed8e468113cd32..ce95b79e18d47915e2eecdef309a73b64417d53c"
+ "shas": "f70c47ebd50d4c6a193f45e79414ba29cb16e719..bf45487f8f0f916e3bbd3a0b39f3dea7f723e069"
}
,{
"testCaseDescription": "javascript-template-string-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/template-string.js b/template-string.js",
- "index 399f117..e69de29 100644",
+ "index 399f1173..e69de29b 100644",
"--- a/template-string.js",
"+++ b/template-string.js",
"@@ -1 +0,0 @@",
"-`multi line`"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ce95b79e18d47915e2eecdef309a73b64417d53c..75f87f22428c68545ebb3f876a1b09caf59d75c9"
+ "shas": "bf45487f8f0f916e3bbd3a0b39f3dea7f723e069..6e93ce14abfffa0befb5a6168efdc830619e0319"
}]
diff --git a/test/corpus/diff-summaries/javascript/ternary.json b/test/corpus/diff-summaries/javascript/ternary.json
index bdaf1034b..ca97f51ec 100644
--- a/test/corpus/diff-summaries/javascript/ternary.json
+++ b/test/corpus/diff-summaries/javascript/ternary.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/ternary.js b/ternary.js",
- "index e69de29..a62be2e 100644",
+ "index e69de29b..a62be2e8 100644",
"--- a/ternary.js",
"+++ b/ternary.js",
"@@ -0,0 +1 @@",
"+condition ? case1 : case2;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0ccf8092231ebc8ac92cc60fe614f1681bc03a89..9667649b2849f1e590a44feec0a6c62c3c2135cc"
+ "shas": "4e62b822a53dcb5dd4c87ffe6ce9db53015fdc68..2ae19d57693a4c8ca756001b6b48f6e936740a55"
}
,{
"testCaseDescription": "javascript-ternary-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/ternary.js b/ternary.js",
- "index a62be2e..17b4f8e 100644",
+ "index a62be2e8..17b4f8ec 100644",
"--- a/ternary.js",
"+++ b/ternary.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" condition ? case1 : case2;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9667649b2849f1e590a44feec0a6c62c3c2135cc..3d5e67c4dc00b3bbf85a3bbe1afd847c77703bbf"
+ "shas": "2ae19d57693a4c8ca756001b6b48f6e936740a55..ae739fd2f744a146f591da9561093cf96069c610"
}
,{
"testCaseDescription": "javascript-ternary-delete-insert-test",
@@ -135,7 +135,7 @@
],
"patch": [
"diff --git a/ternary.js b/ternary.js",
- "index 17b4f8e..aedee54 100644",
+ "index 17b4f8ec..aedee547 100644",
"--- a/ternary.js",
"+++ b/ternary.js",
"@@ -1,3 +1,3 @@",
@@ -145,7 +145,7 @@
" condition ? case1 : case2;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "3d5e67c4dc00b3bbf85a3bbe1afd847c77703bbf..6cba7001515f3956a69b73f69608b7cca7f625f0"
+ "shas": "ae739fd2f744a146f591da9561093cf96069c610..1ba138aca37ffcddced193a0e262be37cb35f944"
}
,{
"testCaseDescription": "javascript-ternary-replacement-test",
@@ -191,7 +191,7 @@
],
"patch": [
"diff --git a/ternary.js b/ternary.js",
- "index aedee54..17b4f8e 100644",
+ "index aedee547..17b4f8ec 100644",
"--- a/ternary.js",
"+++ b/ternary.js",
"@@ -1,3 +1,3 @@",
@@ -201,7 +201,7 @@
" condition ? case1 : case2;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6cba7001515f3956a69b73f69608b7cca7f625f0..7e01f0008705a5f7ffced4f2b9cfaf1431c408fb"
+ "shas": "1ba138aca37ffcddced193a0e262be37cb35f944..14d00728c7ffd0cd5f0aeb16b84f8ed26f36c7ef"
}
,{
"testCaseDescription": "javascript-ternary-delete-replacement-test",
@@ -262,7 +262,7 @@
],
"patch": [
"diff --git a/ternary.js b/ternary.js",
- "index 17b4f8e..6fa999d 100644",
+ "index 17b4f8ec..6fa999d8 100644",
"--- a/ternary.js",
"+++ b/ternary.js",
"@@ -1,3 +1,2 @@",
@@ -272,7 +272,7 @@
"+x.y = some.condition ? some.case : some.other.case;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7e01f0008705a5f7ffced4f2b9cfaf1431c408fb..7d3393632b17cc8c73de9dac1a7538f7fd60e2ca"
+ "shas": "14d00728c7ffd0cd5f0aeb16b84f8ed26f36c7ef..fa19f29bc6742e8ec872791921d2fe24818ef44b"
}
,{
"testCaseDescription": "javascript-ternary-delete-test",
@@ -303,7 +303,7 @@
],
"patch": [
"diff --git a/ternary.js b/ternary.js",
- "index 6fa999d..b63b46d 100644",
+ "index 6fa999d8..b63b46d5 100644",
"--- a/ternary.js",
"+++ b/ternary.js",
"@@ -1,2 +1 @@",
@@ -311,7 +311,7 @@
" x.y = some.condition ? some.case : some.other.case;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7d3393632b17cc8c73de9dac1a7538f7fd60e2ca..361260c5dc31603f665fefc889640330903dbafd"
+ "shas": "fa19f29bc6742e8ec872791921d2fe24818ef44b..aba977b584f40f3b14b24fe9b01c1258398062e4"
}
,{
"testCaseDescription": "javascript-ternary-delete-rest-test",
@@ -342,12 +342,12 @@
],
"patch": [
"diff --git a/ternary.js b/ternary.js",
- "index b63b46d..e69de29 100644",
+ "index b63b46d5..e69de29b 100644",
"--- a/ternary.js",
"+++ b/ternary.js",
"@@ -1 +0,0 @@",
"-x.y = some.condition ? some.case : some.other.case;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "361260c5dc31603f665fefc889640330903dbafd..38dbecd6735244d4c2c50c6608e64fd7df72b900"
+ "shas": "aba977b584f40f3b14b24fe9b01c1258398062e4..ea28b825daec34e8358e77a55a2887289a11b3cd"
}]
diff --git a/test/corpus/diff-summaries/javascript/this-expression.json b/test/corpus/diff-summaries/javascript/this-expression.json
index c15e3aec7..9336fb6b9 100644
--- a/test/corpus/diff-summaries/javascript/this-expression.json
+++ b/test/corpus/diff-summaries/javascript/this-expression.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/this-expression.js b/this-expression.js",
- "index e69de29..b251f26 100644",
+ "index e69de29b..b251f26b 100644",
"--- a/this-expression.js",
"+++ b/this-expression.js",
"@@ -0,0 +1 @@",
"+this;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5180fa74c7ae39b3c2cb94b9b5498307af385e5c..98e4bf8c567fd1203aa3d1c3b9e9dc58d5733e11"
+ "shas": "62c20bfb9474af540a2ab5d5be1a93530bd21eb8..66ca3b368527df8388bd77d1cb4e5e9a299f54b6"
}
,{
"testCaseDescription": "javascript-this-expression-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/this-expression.js b/this-expression.js",
- "index b251f26..5804743 100644",
+ "index b251f26b..58047437 100644",
"--- a/this-expression.js",
"+++ b/this-expression.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" this;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "98e4bf8c567fd1203aa3d1c3b9e9dc58d5733e11..9dd112b28d5a97a59a847018e58f3926ccf46e56"
+ "shas": "66ca3b368527df8388bd77d1cb4e5e9a299f54b6..de28d1ace4687f9b41b4a08f04128d64f0ae0c99"
}
,{
"testCaseDescription": "javascript-this-expression-delete-insert-test",
@@ -135,7 +135,7 @@
],
"patch": [
"diff --git a/this-expression.js b/this-expression.js",
- "index 5804743..3c82a23 100644",
+ "index 58047437..3c82a23c 100644",
"--- a/this-expression.js",
"+++ b/this-expression.js",
"@@ -1,3 +1,3 @@",
@@ -145,7 +145,7 @@
" this;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9dd112b28d5a97a59a847018e58f3926ccf46e56..d1b36cdc475a6f7ea16558b4269f3e3c18758dfa"
+ "shas": "de28d1ace4687f9b41b4a08f04128d64f0ae0c99..f76ef95549e8ec4477ab6caf90dd759cf159abb7"
}
,{
"testCaseDescription": "javascript-this-expression-replacement-test",
@@ -191,7 +191,7 @@
],
"patch": [
"diff --git a/this-expression.js b/this-expression.js",
- "index 3c82a23..5804743 100644",
+ "index 3c82a23c..58047437 100644",
"--- a/this-expression.js",
"+++ b/this-expression.js",
"@@ -1,3 +1,3 @@",
@@ -201,7 +201,7 @@
" this;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d1b36cdc475a6f7ea16558b4269f3e3c18758dfa..efc36cfae7c31ef3d4f2052a0c79fe592ab2aa58"
+ "shas": "f76ef95549e8ec4477ab6caf90dd759cf159abb7..bea9b6c56f0741d236b23a7bacba139f80bc197e"
}
,{
"testCaseDescription": "javascript-this-expression-delete-replacement-test",
@@ -262,7 +262,7 @@
],
"patch": [
"diff --git a/this-expression.js b/this-expression.js",
- "index 5804743..81aca89 100644",
+ "index 58047437..81aca892 100644",
"--- a/this-expression.js",
"+++ b/this-expression.js",
"@@ -1,3 +1,2 @@",
@@ -272,7 +272,7 @@
"+return this;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "efc36cfae7c31ef3d4f2052a0c79fe592ab2aa58..531a5b86388175804b734a10ace1c7645169154b"
+ "shas": "bea9b6c56f0741d236b23a7bacba139f80bc197e..238bbfa9cb9a73ac6f0095dd2ec9e541ba829a80"
}
,{
"testCaseDescription": "javascript-this-expression-delete-test",
@@ -303,7 +303,7 @@
],
"patch": [
"diff --git a/this-expression.js b/this-expression.js",
- "index 81aca89..45c3231 100644",
+ "index 81aca892..45c3231b 100644",
"--- a/this-expression.js",
"+++ b/this-expression.js",
"@@ -1,2 +1 @@",
@@ -311,7 +311,7 @@
" return this;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "531a5b86388175804b734a10ace1c7645169154b..dfa50df5733740923a1d747f988102b19e9ce7e0"
+ "shas": "238bbfa9cb9a73ac6f0095dd2ec9e541ba829a80..4493a43c8cfab7b560393189918ac5233e131700"
}
,{
"testCaseDescription": "javascript-this-expression-delete-rest-test",
@@ -342,12 +342,12 @@
],
"patch": [
"diff --git a/this-expression.js b/this-expression.js",
- "index 45c3231..e69de29 100644",
+ "index 45c3231b..e69de29b 100644",
"--- a/this-expression.js",
"+++ b/this-expression.js",
"@@ -1 +0,0 @@",
"-return this;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "dfa50df5733740923a1d747f988102b19e9ce7e0..655d7887b70794042aa3e0f4d6ea174c1b32af1c"
+ "shas": "4493a43c8cfab7b560393189918ac5233e131700..da816fd1d09e1ffe56fc188b498a7f2312d7d0f2"
}]
diff --git a/test/corpus/diff-summaries/javascript/throw-statement.json b/test/corpus/diff-summaries/javascript/throw-statement.json
index 9d7d995c0..b7c82ff59 100644
--- a/test/corpus/diff-summaries/javascript/throw-statement.json
+++ b/test/corpus/diff-summaries/javascript/throw-statement.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/throw-statement.js b/throw-statement.js",
- "index e69de29..e2fcb67 100644",
+ "index e69de29b..e2fcb67e 100644",
"--- a/throw-statement.js",
"+++ b/throw-statement.js",
"@@ -0,0 +1 @@",
"+throw new Error(\"uh oh\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8e3f45940f773e7849a53fefdaeb52a682a6a488..116eb17be5e023970df37ba38884c86aa4cb9dbd"
+ "shas": "20c612d09dbfc0c2c4ab61b7c9234d17faa3f43e..4c4b9cfa76e0341cd6b2773ed2f4fee6cbba6801"
}
,{
"testCaseDescription": "javascript-throw-statement-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/throw-statement.js b/throw-statement.js",
- "index e2fcb67..c0020c8 100644",
+ "index e2fcb67e..c0020c89 100644",
"--- a/throw-statement.js",
"+++ b/throw-statement.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" throw new Error(\"uh oh\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "116eb17be5e023970df37ba38884c86aa4cb9dbd..e1a31ba713d3185c274f86dd4e8644740fb7429d"
+ "shas": "4c4b9cfa76e0341cd6b2773ed2f4fee6cbba6801..c4cf5d1a0e5380b0fe9170d3f3d3f452f96ff051"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/throw-statement.js b/throw-statement.js",
- "index c0020c8..4644233 100644",
+ "index c0020c89..46442332 100644",
"--- a/throw-statement.js",
"+++ b/throw-statement.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" throw new Error(\"uh oh\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "e1a31ba713d3185c274f86dd4e8644740fb7429d..dad40ac44ee1763621da95939261c0afc7664ec4"
+ "shas": "c4cf5d1a0e5380b0fe9170d3f3d3f452f96ff051..cb3c1b253c771eeb846b64affb12b6986c40977a"
}
,{
"testCaseDescription": "javascript-throw-statement-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/throw-statement.js b/throw-statement.js",
- "index 4644233..c0020c8 100644",
+ "index 46442332..c0020c89 100644",
"--- a/throw-statement.js",
"+++ b/throw-statement.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" throw new Error(\"uh oh\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "dad40ac44ee1763621da95939261c0afc7664ec4..6ead807809e97520b2dce628bc592bfa358dd249"
+ "shas": "cb3c1b253c771eeb846b64affb12b6986c40977a..ecbbfb90f3448338b540960be008bbcad8bb7d54"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/throw-statement.js b/throw-statement.js",
- "index c0020c8..a1bbf3e 100644",
+ "index c0020c89..a1bbf3e1 100644",
"--- a/throw-statement.js",
"+++ b/throw-statement.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+throw new Error(\"oooooops\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "6ead807809e97520b2dce628bc592bfa358dd249..c1804715b17f4c02c529052b13f67eab4f85d127"
+ "shas": "ecbbfb90f3448338b540960be008bbcad8bb7d54..a78d37a5473fa63f59d233127cab6692ca1f7bb8"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/throw-statement.js b/throw-statement.js",
- "index a1bbf3e..cc3c531 100644",
+ "index a1bbf3e1..cc3c5312 100644",
"--- a/throw-statement.js",
"+++ b/throw-statement.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" throw new Error(\"oooooops\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "c1804715b17f4c02c529052b13f67eab4f85d127..36892466e1b20aa85270c797d4898149a5456dae"
+ "shas": "a78d37a5473fa63f59d233127cab6692ca1f7bb8..7318e2a144a5c550ebbafb4bc615fa30fabea266"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/throw-statement.js b/throw-statement.js",
- "index cc3c531..e69de29 100644",
+ "index cc3c5312..e69de29b 100644",
"--- a/throw-statement.js",
"+++ b/throw-statement.js",
"@@ -1 +0,0 @@",
"-throw new Error(\"oooooops\");"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "36892466e1b20aa85270c797d4898149a5456dae..a5583b5ba5ae300bddff029cb144c539a2cb48fd"
+ "shas": "7318e2a144a5c550ebbafb4bc615fa30fabea266..4d5c25eaa453b756183d88d10a8fa94ec9a29ce9"
}]
diff --git a/test/corpus/diff-summaries/javascript/true.json b/test/corpus/diff-summaries/javascript/true.json
index 198bd4dfe..0ca9041f5 100644
--- a/test/corpus/diff-summaries/javascript/true.json
+++ b/test/corpus/diff-summaries/javascript/true.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/true.js b/true.js",
- "index e69de29..4203d4b 100644",
+ "index e69de29b..4203d4b4 100644",
"--- a/true.js",
"+++ b/true.js",
"@@ -0,0 +1 @@",
"+true;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "bc804312603351b07d0e242d9b3675d646934512..b8a5a66ee0d580e0f5be577ba65a6afe82b8acfe"
+ "shas": "a392bcd691680203eae2c96e73b145e2140a6097..206061601a6b3f269fd703d097e2d5f1b8baaecc"
}
,{
"testCaseDescription": "javascript-true-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/true.js b/true.js",
- "index 4203d4b..65b6323 100644",
+ "index 4203d4b4..65b6323f 100644",
"--- a/true.js",
"+++ b/true.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" true;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "b8a5a66ee0d580e0f5be577ba65a6afe82b8acfe..38f0052081cce419eb03bcd07164a3f756a4d014"
+ "shas": "206061601a6b3f269fd703d097e2d5f1b8baaecc..edde8c160a81303c26e3ea28a3eb50773592c49b"
}
,{
"testCaseDescription": "javascript-true-delete-insert-test",
@@ -135,7 +135,7 @@
],
"patch": [
"diff --git a/true.js b/true.js",
- "index 65b6323..91e1cfc 100644",
+ "index 65b6323f..91e1cfc7 100644",
"--- a/true.js",
"+++ b/true.js",
"@@ -1,3 +1,3 @@",
@@ -145,7 +145,7 @@
" true;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "38f0052081cce419eb03bcd07164a3f756a4d014..514cc9bcf90d8b96eb0f5109b0c84d8136f5e82a"
+ "shas": "edde8c160a81303c26e3ea28a3eb50773592c49b..9335dec627559608ccca695be2c4cffb46c6cd69"
}
,{
"testCaseDescription": "javascript-true-replacement-test",
@@ -191,7 +191,7 @@
],
"patch": [
"diff --git a/true.js b/true.js",
- "index 91e1cfc..65b6323 100644",
+ "index 91e1cfc7..65b6323f 100644",
"--- a/true.js",
"+++ b/true.js",
"@@ -1,3 +1,3 @@",
@@ -201,7 +201,7 @@
" true;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "514cc9bcf90d8b96eb0f5109b0c84d8136f5e82a..883bffa8136e0f6cc1fc850f8aab8f69ac48699b"
+ "shas": "9335dec627559608ccca695be2c4cffb46c6cd69..2063519ea7d98f18154478774046117b4d6eb125"
}
,{
"testCaseDescription": "javascript-true-delete-replacement-test",
@@ -262,7 +262,7 @@
],
"patch": [
"diff --git a/true.js b/true.js",
- "index 65b6323..48a44d1 100644",
+ "index 65b6323f..48a44d12 100644",
"--- a/true.js",
"+++ b/true.js",
"@@ -1,3 +1,2 @@",
@@ -272,7 +272,7 @@
"+return true;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "883bffa8136e0f6cc1fc850f8aab8f69ac48699b..36585335908145fbf9f18eabecb60038b29552f0"
+ "shas": "2063519ea7d98f18154478774046117b4d6eb125..304c73f27e3a9f945bdbeecf6be10e042990af21"
}
,{
"testCaseDescription": "javascript-true-delete-test",
@@ -303,7 +303,7 @@
],
"patch": [
"diff --git a/true.js b/true.js",
- "index 48a44d1..c1c6922 100644",
+ "index 48a44d12..c1c6922d 100644",
"--- a/true.js",
"+++ b/true.js",
"@@ -1,2 +1 @@",
@@ -311,7 +311,7 @@
" return true;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "36585335908145fbf9f18eabecb60038b29552f0..9d5dc3e57ffd189e1482d577bfc73e78e900d42a"
+ "shas": "304c73f27e3a9f945bdbeecf6be10e042990af21..465c4b4873ceea8d4e7b205428cf5a5d252b0428"
}
,{
"testCaseDescription": "javascript-true-delete-rest-test",
@@ -342,12 +342,12 @@
],
"patch": [
"diff --git a/true.js b/true.js",
- "index c1c6922..e69de29 100644",
+ "index c1c6922d..e69de29b 100644",
"--- a/true.js",
"+++ b/true.js",
"@@ -1 +0,0 @@",
"-return true;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9d5dc3e57ffd189e1482d577bfc73e78e900d42a..a56c14e19dec2910d36460e4fca6496da46f6240"
+ "shas": "465c4b4873ceea8d4e7b205428cf5a5d252b0428..d7a5c35ea0a826299a22c96d0b992f92bc85bb91"
}]
diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json
index 80e94c7ff..0820adb60 100644
--- a/test/corpus/diff-summaries/javascript/try-statement.json
+++ b/test/corpus/diff-summaries/javascript/try-statement.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/try-statement.js b/try-statement.js",
- "index e69de29..9826f7c 100644",
+ "index e69de29b..9826f7c2 100644",
"--- a/try-statement.js",
"+++ b/try-statement.js",
"@@ -0,0 +1 @@",
"+try { f; } catch { g; } finally { h; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "a5583b5ba5ae300bddff029cb144c539a2cb48fd..d8b7dc1823e1a5b0909865b2d0d40a40f0185e59"
+ "shas": "4d5c25eaa453b756183d88d10a8fa94ec9a29ce9..7bb26d4337edf14203a2a3b262d5935118330d15"
}
,{
"testCaseDescription": "javascript-try-statement-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/try-statement.js b/try-statement.js",
- "index 9826f7c..7befc1c 100644",
+ "index 9826f7c2..7befc1c1 100644",
"--- a/try-statement.js",
"+++ b/try-statement.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" try { f; } catch { g; } finally { h; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d8b7dc1823e1a5b0909865b2d0d40a40f0185e59..670f6360d76e32d78de98aae0552d153f8dc9a90"
+ "shas": "7bb26d4337edf14203a2a3b262d5935118330d15..ee7528fb533bc95066de6d7169b854055e82cdff"
}
,{
"testCaseDescription": "javascript-try-statement-delete-insert-test",
@@ -159,7 +159,7 @@
],
"patch": [
"diff --git a/try-statement.js b/try-statement.js",
- "index 7befc1c..94fed9c 100644",
+ "index 7befc1c1..94fed9ce 100644",
"--- a/try-statement.js",
"+++ b/try-statement.js",
"@@ -1,3 +1,3 @@",
@@ -169,7 +169,7 @@
" try { f; } catch { g; } finally { h; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "670f6360d76e32d78de98aae0552d153f8dc9a90..64175cdf26b3a3618ea930a705a043f895b3fd09"
+ "shas": "ee7528fb533bc95066de6d7169b854055e82cdff..221a16801cd06b97641ed047442d1867348bc4f2"
}
,{
"testCaseDescription": "javascript-try-statement-replacement-test",
@@ -239,7 +239,7 @@
],
"patch": [
"diff --git a/try-statement.js b/try-statement.js",
- "index 94fed9c..7befc1c 100644",
+ "index 94fed9ce..7befc1c1 100644",
"--- a/try-statement.js",
"+++ b/try-statement.js",
"@@ -1,3 +1,3 @@",
@@ -249,7 +249,7 @@
" try { f; } catch { g; } finally { h; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "64175cdf26b3a3618ea930a705a043f895b3fd09..42c1509a343741e5dd1c1bfcb86fb8745b60824d"
+ "shas": "221a16801cd06b97641ed047442d1867348bc4f2..fe8d10b8b7f98496e7cee7d9242c1420fc48b3d4"
}
,{
"testCaseDescription": "javascript-try-statement-delete-replacement-test",
@@ -310,7 +310,7 @@
],
"patch": [
"diff --git a/try-statement.js b/try-statement.js",
- "index 7befc1c..8ab70e0 100644",
+ "index 7befc1c1..8ab70e04 100644",
"--- a/try-statement.js",
"+++ b/try-statement.js",
"@@ -1,3 +1,2 @@",
@@ -320,7 +320,7 @@
"+try { f; } catch { h; } finally { g; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "42c1509a343741e5dd1c1bfcb86fb8745b60824d..400e89f91ea35a78dd70b46c3bc204c5aed26b7f"
+ "shas": "fe8d10b8b7f98496e7cee7d9242c1420fc48b3d4..3e20f543dcd7595ce0dac8272cdf0e386e7d2a72"
}
,{
"testCaseDescription": "javascript-try-statement-delete-test",
@@ -351,7 +351,7 @@
],
"patch": [
"diff --git a/try-statement.js b/try-statement.js",
- "index 8ab70e0..024f88a 100644",
+ "index 8ab70e04..024f88ab 100644",
"--- a/try-statement.js",
"+++ b/try-statement.js",
"@@ -1,2 +1 @@",
@@ -359,7 +359,7 @@
" try { f; } catch { h; } finally { g; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "400e89f91ea35a78dd70b46c3bc204c5aed26b7f..f97dd13575c5a030192a9abd5e4992a51afc050f"
+ "shas": "3e20f543dcd7595ce0dac8272cdf0e386e7d2a72..dd3aa2655f6d2ae0765b9eac73f8789b3790e3d2"
}
,{
"testCaseDescription": "javascript-try-statement-delete-rest-test",
@@ -390,12 +390,12 @@
],
"patch": [
"diff --git a/try-statement.js b/try-statement.js",
- "index 024f88a..e69de29 100644",
+ "index 024f88ab..e69de29b 100644",
"--- a/try-statement.js",
"+++ b/try-statement.js",
"@@ -1 +0,0 @@",
"-try { f; } catch { h; } finally { g; };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f97dd13575c5a030192a9abd5e4992a51afc050f..734bede3c6c3771f011aa729a417011d310ec5cc"
+ "shas": "dd3aa2655f6d2ae0765b9eac73f8789b3790e3d2..821df9c41798fbc70ad5ca5a5795c00b2cedb79c"
}]
diff --git a/test/corpus/diff-summaries/javascript/type-operator.json b/test/corpus/diff-summaries/javascript/type-operator.json
index 1a0568f94..6197321b0 100644
--- a/test/corpus/diff-summaries/javascript/type-operator.json
+++ b/test/corpus/diff-summaries/javascript/type-operator.json
@@ -34,7 +34,7 @@
"+typeof x;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8a27197df5dd32970d666dec2ed87840381ee268..022b10ca6587ce508c5c19c8b4ce3eda620bb06d"
+ "shas": "ea28b825daec34e8358e77a55a2887289a11b3cd..5095bc1189bb6b8c9b262e2a69bcb913e12987f6"
}
,{
"testCaseDescription": "javascript-type-operator-replacement-insert-test",
@@ -89,7 +89,7 @@
" typeof x;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "022b10ca6587ce508c5c19c8b4ce3eda620bb06d..5d3e102e26668c0582da052a846ae6b4965f80dc"
+ "shas": "5095bc1189bb6b8c9b262e2a69bcb913e12987f6..81327c4f649a78442d83120079c47474f97c6ffe"
}
,{
"testCaseDescription": "javascript-type-operator-delete-insert-test",
@@ -142,7 +142,7 @@
" typeof x;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5d3e102e26668c0582da052a846ae6b4965f80dc..80ee88adb73c66f5d7f8e7ad2d462ba95656a35f"
+ "shas": "81327c4f649a78442d83120079c47474f97c6ffe..dcc3b0a273577c402eb9b04ef2c4e8913bc33225"
}
,{
"testCaseDescription": "javascript-type-operator-replacement-test",
@@ -195,7 +195,7 @@
" typeof x;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "80ee88adb73c66f5d7f8e7ad2d462ba95656a35f..7dba6ba536a93671b81505e98ffc137d51714936"
+ "shas": "dcc3b0a273577c402eb9b04ef2c4e8913bc33225..9b13edcaadcd83ceb4e87af5c0d2b0e6c1d7adbe"
}
,{
"testCaseDescription": "javascript-type-operator-delete-replacement-test",
@@ -266,7 +266,7 @@
"+x instanceof String;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7dba6ba536a93671b81505e98ffc137d51714936..9426a9f8c4206d41610d24729659aabd8bb92f4d"
+ "shas": "9b13edcaadcd83ceb4e87af5c0d2b0e6c1d7adbe..5f6fd5e4183d7c61b67840a4c1cedb6f41a2b453"
}
,{
"testCaseDescription": "javascript-type-operator-delete-test",
@@ -305,7 +305,7 @@
" x instanceof String;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9426a9f8c4206d41610d24729659aabd8bb92f4d..4dea2afbe25572aee977123753ff00348123b34d"
+ "shas": "5f6fd5e4183d7c61b67840a4c1cedb6f41a2b453..d64c2126b4849fe4ce74bec3807124a1ddd05734"
}
,{
"testCaseDescription": "javascript-type-operator-delete-rest-test",
@@ -343,5 +343,5 @@
"-x instanceof String;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4dea2afbe25572aee977123753ff00348123b34d..5fe71a17cc99387501792a564bc50da57decd600"
+ "shas": "d64c2126b4849fe4ce74bec3807124a1ddd05734..40c56c88e1737aa2249e65bf6883ae636953376f"
}]
diff --git a/test/corpus/diff-summaries/javascript/undefined.json b/test/corpus/diff-summaries/javascript/undefined.json
index 1e99c042f..9cd04f3d6 100644
--- a/test/corpus/diff-summaries/javascript/undefined.json
+++ b/test/corpus/diff-summaries/javascript/undefined.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/undefined.js b/undefined.js",
- "index e69de29..c2ca02c 100644",
+ "index e69de29b..c2ca02c0 100644",
"--- a/undefined.js",
"+++ b/undefined.js",
"@@ -0,0 +1 @@",
"+undefined;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "9f36bd70533d2f145bb9661791f0ea760bf949d5..5ea4083212daf3e2a900de3b68508a604ade8596"
+ "shas": "2f535d692705ba01866febca83c7f3cb4af53987..9de3a467dad18d25a0078562813cd594d58045ce"
}
,{
"testCaseDescription": "javascript-undefined-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/undefined.js b/undefined.js",
- "index c2ca02c..a4352cc 100644",
+ "index c2ca02c0..a4352cc6 100644",
"--- a/undefined.js",
"+++ b/undefined.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" undefined;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5ea4083212daf3e2a900de3b68508a604ade8596..d6cc7e90bce713f04bcfee5d53e1a112b1bfad0a"
+ "shas": "9de3a467dad18d25a0078562813cd594d58045ce..17b5b8536a51cabab8246dc59dc9201c0003313d"
}
,{
"testCaseDescription": "javascript-undefined-delete-insert-test",
@@ -135,7 +135,7 @@
],
"patch": [
"diff --git a/undefined.js b/undefined.js",
- "index a4352cc..52ea257 100644",
+ "index a4352cc6..52ea2570 100644",
"--- a/undefined.js",
"+++ b/undefined.js",
"@@ -1,3 +1,3 @@",
@@ -145,7 +145,7 @@
" undefined;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d6cc7e90bce713f04bcfee5d53e1a112b1bfad0a..718b0c7d530a5e063201c119f59091b97d0e90d3"
+ "shas": "17b5b8536a51cabab8246dc59dc9201c0003313d..10e4daeebb1d2b7786f7a7e5fae43a385069c4f0"
}
,{
"testCaseDescription": "javascript-undefined-replacement-test",
@@ -191,7 +191,7 @@
],
"patch": [
"diff --git a/undefined.js b/undefined.js",
- "index 52ea257..a4352cc 100644",
+ "index 52ea2570..a4352cc6 100644",
"--- a/undefined.js",
"+++ b/undefined.js",
"@@ -1,3 +1,3 @@",
@@ -201,7 +201,7 @@
" undefined;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "718b0c7d530a5e063201c119f59091b97d0e90d3..829fc4f00b66a91b67b0d0d41023f3d48fb34aa8"
+ "shas": "10e4daeebb1d2b7786f7a7e5fae43a385069c4f0..2fae14567b855fb189bc24a23969bfb106e2c8cd"
}
,{
"testCaseDescription": "javascript-undefined-delete-replacement-test",
@@ -262,7 +262,7 @@
],
"patch": [
"diff --git a/undefined.js b/undefined.js",
- "index a4352cc..a16e747 100644",
+ "index a4352cc6..a16e7474 100644",
"--- a/undefined.js",
"+++ b/undefined.js",
"@@ -1,3 +1,2 @@",
@@ -272,7 +272,7 @@
"+return undefined;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "829fc4f00b66a91b67b0d0d41023f3d48fb34aa8..ca6a3d94c002135dcd0d1096f808eadb016c1adf"
+ "shas": "2fae14567b855fb189bc24a23969bfb106e2c8cd..3f9e6ae65c8c8e3767f7b6a3eb497cea9274b8d7"
}
,{
"testCaseDescription": "javascript-undefined-delete-test",
@@ -303,7 +303,7 @@
],
"patch": [
"diff --git a/undefined.js b/undefined.js",
- "index a16e747..fb505bb 100644",
+ "index a16e7474..fb505bb3 100644",
"--- a/undefined.js",
"+++ b/undefined.js",
"@@ -1,2 +1 @@",
@@ -311,7 +311,7 @@
" return undefined;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "ca6a3d94c002135dcd0d1096f808eadb016c1adf..2952f11c8fb57194cae4acde26f39231327790b0"
+ "shas": "3f9e6ae65c8c8e3767f7b6a3eb497cea9274b8d7..1d4739ce9a7c85726b2aa04a115b6eec5be43bd5"
}
,{
"testCaseDescription": "javascript-undefined-delete-rest-test",
@@ -342,12 +342,12 @@
],
"patch": [
"diff --git a/undefined.js b/undefined.js",
- "index fb505bb..e69de29 100644",
+ "index fb505bb3..e69de29b 100644",
"--- a/undefined.js",
"+++ b/undefined.js",
"@@ -1 +0,0 @@",
"-return undefined;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2952f11c8fb57194cae4acde26f39231327790b0..bc804312603351b07d0e242d9b3675d646934512"
+ "shas": "1d4739ce9a7c85726b2aa04a115b6eec5be43bd5..a392bcd691680203eae2c96e73b145e2140a6097"
}]
diff --git a/test/corpus/diff-summaries/javascript/var-declaration.json b/test/corpus/diff-summaries/javascript/var-declaration.json
index 3840b00b0..10d7e51d8 100644
--- a/test/corpus/diff-summaries/javascript/var-declaration.json
+++ b/test/corpus/diff-summaries/javascript/var-declaration.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/var-declaration.js b/var-declaration.js",
- "index e69de29..b506100 100644",
+ "index e69de29b..b506100a 100644",
"--- a/var-declaration.js",
"+++ b/var-declaration.js",
"@@ -0,0 +1 @@",
"+var x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5d2db352ed0e33bb51a7f2330066274984490127..f455ffd086c07cb3e4de74f4da0be7e944d063f7"
+ "shas": "c90fef2277e371c606b2a159aee629c8a43edec2..2495702ca9d23a191988de90eb7f3a8bfc70e3a0"
}
,{
"testCaseDescription": "javascript-var-declaration-replacement-insert-test",
@@ -110,7 +110,7 @@
],
"patch": [
"diff --git a/var-declaration.js b/var-declaration.js",
- "index b506100..b08ebfb 100644",
+ "index b506100a..b08ebfb5 100644",
"--- a/var-declaration.js",
"+++ b/var-declaration.js",
"@@ -1 +1,3 @@",
@@ -119,7 +119,7 @@
" var x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "f455ffd086c07cb3e4de74f4da0be7e944d063f7..7c7c53ef609ab1a3f9dd578a6e7b3af487d1a8d6"
+ "shas": "2495702ca9d23a191988de90eb7f3a8bfc70e3a0..c984808c6c378bed7f694149afddaee99a4afb24"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-insert-test",
@@ -195,7 +195,7 @@
],
"patch": [
"diff --git a/var-declaration.js b/var-declaration.js",
- "index b08ebfb..adc261e 100644",
+ "index b08ebfb5..adc261e0 100644",
"--- a/var-declaration.js",
"+++ b/var-declaration.js",
"@@ -1,3 +1,3 @@",
@@ -205,7 +205,7 @@
" var x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "7c7c53ef609ab1a3f9dd578a6e7b3af487d1a8d6..8c51fa18b7b49a6bb22947979e3660da861b8472"
+ "shas": "c984808c6c378bed7f694149afddaee99a4afb24..6647f6584a6b5827130d523d2b08bbc2cb604d19"
}
,{
"testCaseDescription": "javascript-var-declaration-replacement-test",
@@ -278,7 +278,7 @@
],
"patch": [
"diff --git a/var-declaration.js b/var-declaration.js",
- "index adc261e..b08ebfb 100644",
+ "index adc261e0..b08ebfb5 100644",
"--- a/var-declaration.js",
"+++ b/var-declaration.js",
"@@ -1,3 +1,3 @@",
@@ -288,7 +288,7 @@
" var x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "8c51fa18b7b49a6bb22947979e3660da861b8472..41c866c677aca04b21b600e74d218ccc998d2f5d"
+ "shas": "6647f6584a6b5827130d523d2b08bbc2cb604d19..e92b6cd68605c7cfb2db03501dce8f1e78255155"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-replacement-test",
@@ -409,7 +409,7 @@
],
"patch": [
"diff --git a/var-declaration.js b/var-declaration.js",
- "index b08ebfb..514f7c4 100644",
+ "index b08ebfb5..514f7c48 100644",
"--- a/var-declaration.js",
"+++ b/var-declaration.js",
"@@ -1,3 +1,2 @@",
@@ -419,7 +419,7 @@
"+var x, y = {}, z;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "41c866c677aca04b21b600e74d218ccc998d2f5d..4330d72069a0ee02f257a7a2958054b36255ea3a"
+ "shas": "e92b6cd68605c7cfb2db03501dce8f1e78255155..e8074b6f7a2540990803dba4d0250a7aad94e647"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-test",
@@ -450,7 +450,7 @@
],
"patch": [
"diff --git a/var-declaration.js b/var-declaration.js",
- "index 514f7c4..9fc69e2 100644",
+ "index 514f7c48..9fc69e2f 100644",
"--- a/var-declaration.js",
"+++ b/var-declaration.js",
"@@ -1,2 +1 @@",
@@ -458,7 +458,7 @@
" var x, y = {}, z;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "4330d72069a0ee02f257a7a2958054b36255ea3a..2285435873a4dd3e309e0a9950307823b9f95795"
+ "shas": "e8074b6f7a2540990803dba4d0250a7aad94e647..b679add9a334636a6c2723bdfa2efbfcbf7222d9"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-rest-test",
@@ -519,12 +519,12 @@
],
"patch": [
"diff --git a/var-declaration.js b/var-declaration.js",
- "index 9fc69e2..e69de29 100644",
+ "index 9fc69e2f..e69de29b 100644",
"--- a/var-declaration.js",
"+++ b/var-declaration.js",
"@@ -1 +0,0 @@",
"-var x, y = {}, z;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2285435873a4dd3e309e0a9950307823b9f95795..81bc4513ad3979452e9e95586a5fbc9ca66eeadc"
+ "shas": "b679add9a334636a6c2723bdfa2efbfcbf7222d9..56b3ef654938c8fc1c02e365cb518f170511a823"
}]
diff --git a/test/corpus/diff-summaries/javascript/variable.json b/test/corpus/diff-summaries/javascript/variable.json
index 543761464..758cf09fc 100644
--- a/test/corpus/diff-summaries/javascript/variable.json
+++ b/test/corpus/diff-summaries/javascript/variable.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/variable.js b/variable.js",
- "index e69de29..1cf4ad0 100644",
+ "index e69de29b..1cf4ad05 100644",
"--- a/variable.js",
"+++ b/variable.js",
"@@ -0,0 +1 @@",
"+theVar;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2e348ee88f62c0857d6f6ce2ab3ee0d46f12afeb..09aa9131842b754fdd19963205e4e00f4413871b"
+ "shas": "3ab54dc1f52a044020029364417b8c1e44102ef5..32ffc9016a9036ddef2fce855dbabfb7bd1acd96"
}
,{
"testCaseDescription": "javascript-variable-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/variable.js b/variable.js",
- "index 1cf4ad0..888855a 100644",
+ "index 1cf4ad05..888855ad 100644",
"--- a/variable.js",
"+++ b/variable.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" theVar;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "09aa9131842b754fdd19963205e4e00f4413871b..0b3b0533e575b679bbba53387580ba2c730806e4"
+ "shas": "32ffc9016a9036ddef2fce855dbabfb7bd1acd96..1c41f51366e2e534813ad54543c086b05fd76f42"
}
,{
"testCaseDescription": "javascript-variable-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/variable.js b/variable.js",
- "index 888855a..60e041c 100644",
+ "index 888855ad..60e041c1 100644",
"--- a/variable.js",
"+++ b/variable.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" theVar;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0b3b0533e575b679bbba53387580ba2c730806e4..03875ee2891e9d8081f5d4bace0acb59724eca90"
+ "shas": "1c41f51366e2e534813ad54543c086b05fd76f42..6c615ecd1b0e89f5a89aac59f6e3dcea0e53d3b7"
}
,{
"testCaseDescription": "javascript-variable-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/variable.js b/variable.js",
- "index 60e041c..888855a 100644",
+ "index 60e041c1..888855ad 100644",
"--- a/variable.js",
"+++ b/variable.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" theVar;"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "03875ee2891e9d8081f5d4bace0acb59724eca90..fc9c0d118d51bb745bf3665c575c58592deee4d5"
+ "shas": "6c615ecd1b0e89f5a89aac59f6e3dcea0e53d3b7..4e54a7bf031d9056ade28569e9a7c8b8aab05a48"
}
,{
"testCaseDescription": "javascript-variable-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/variable.js b/variable.js",
- "index 888855a..fbc7b28 100644",
+ "index 888855ad..fbc7b28e 100644",
"--- a/variable.js",
"+++ b/variable.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+theVar2"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "fc9c0d118d51bb745bf3665c575c58592deee4d5..e286370e12767dd248982f92fd5f058e1099616e"
+ "shas": "4e54a7bf031d9056ade28569e9a7c8b8aab05a48..7fc8f379d2c5b766bf4e55da23d7b31726406bd9"
}
,{
"testCaseDescription": "javascript-variable-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/variable.js b/variable.js",
- "index fbc7b28..7276d95 100644",
+ "index fbc7b28e..7276d95d 100644",
"--- a/variable.js",
"+++ b/variable.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" theVar2"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "e286370e12767dd248982f92fd5f058e1099616e..841c185fa272c7e634d52eca4fd38d05c1ac72a4"
+ "shas": "7fc8f379d2c5b766bf4e55da23d7b31726406bd9..8a05285735f7169959851e97686b3b2225b0fd59"
}
,{
"testCaseDescription": "javascript-variable-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/variable.js b/variable.js",
- "index 7276d95..e69de29 100644",
+ "index 7276d95d..e69de29b 100644",
"--- a/variable.js",
"+++ b/variable.js",
"@@ -1 +0,0 @@",
"-theVar2"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "841c185fa272c7e634d52eca4fd38d05c1ac72a4..2642fef686808ac2a6c5edde323e87257f4f2983"
+ "shas": "8a05285735f7169959851e97686b3b2225b0fd59..23f245e71b4513803366aff2b4ae93549ad9d3fa"
}]
diff --git a/test/corpus/diff-summaries/javascript/void-operator.json b/test/corpus/diff-summaries/javascript/void-operator.json
index 5bcbc9d50..73bbb8f60 100644
--- a/test/corpus/diff-summaries/javascript/void-operator.json
+++ b/test/corpus/diff-summaries/javascript/void-operator.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/void-operator.js b/void-operator.js",
- "index e69de29..02aa750 100644",
+ "index e69de29b..02aa7503 100644",
"--- a/void-operator.js",
"+++ b/void-operator.js",
"@@ -0,0 +1 @@",
"+void b()"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "56f88d5286e94da2b11b7f6d0a35aa836d4f5921..090251ad4b6d167fb4a8ada452c235f6ef453446"
+ "shas": "f90555ef6eea69038b7aa16bd074797419738b0a..1f8b21c36e0802112f4265ea647dd2d5d362a272"
}
,{
"testCaseDescription": "javascript-void-operator-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/void-operator.js b/void-operator.js",
- "index 02aa750..c493dc5 100644",
+ "index 02aa7503..c493dc5b 100644",
"--- a/void-operator.js",
"+++ b/void-operator.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" void b()"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "090251ad4b6d167fb4a8ada452c235f6ef453446..bf6411aac8dfb3eeb0f991114c7f48b390b61430"
+ "shas": "1f8b21c36e0802112f4265ea647dd2d5d362a272..2f15c4cedbca086328f2f92442f67263fbcd29bc"
}
,{
"testCaseDescription": "javascript-void-operator-delete-insert-test",
@@ -132,7 +132,7 @@
],
"patch": [
"diff --git a/void-operator.js b/void-operator.js",
- "index c493dc5..aae2f63 100644",
+ "index c493dc5b..aae2f633 100644",
"--- a/void-operator.js",
"+++ b/void-operator.js",
"@@ -1,3 +1,3 @@",
@@ -142,7 +142,7 @@
" void b()"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "bf6411aac8dfb3eeb0f991114c7f48b390b61430..d00f222abddf5191477b57afc4101cf73ee16ec5"
+ "shas": "2f15c4cedbca086328f2f92442f67263fbcd29bc..d645696290851ecc05cc5dc535d1ac1816accd63"
}
,{
"testCaseDescription": "javascript-void-operator-replacement-test",
@@ -185,7 +185,7 @@
],
"patch": [
"diff --git a/void-operator.js b/void-operator.js",
- "index aae2f63..c493dc5 100644",
+ "index aae2f633..c493dc5b 100644",
"--- a/void-operator.js",
"+++ b/void-operator.js",
"@@ -1,3 +1,3 @@",
@@ -195,7 +195,7 @@
" void b()"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "d00f222abddf5191477b57afc4101cf73ee16ec5..36271b63277a1739ae109605f2f520baf14525b4"
+ "shas": "d645696290851ecc05cc5dc535d1ac1816accd63..7e7a2bdaab6bcab70474468916bab238da5974b5"
}
,{
"testCaseDescription": "javascript-void-operator-delete-replacement-test",
@@ -256,7 +256,7 @@
],
"patch": [
"diff --git a/void-operator.js b/void-operator.js",
- "index c493dc5..738c34a 100644",
+ "index c493dc5b..738c34a4 100644",
"--- a/void-operator.js",
"+++ b/void-operator.js",
"@@ -1,3 +1,2 @@",
@@ -266,7 +266,7 @@
"+void c()"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "36271b63277a1739ae109605f2f520baf14525b4..350bf156c704fb4f26d0ada86678e654d40d70cc"
+ "shas": "7e7a2bdaab6bcab70474468916bab238da5974b5..8835bba7c5048d609d2eb5e67b0680423893ab3d"
}
,{
"testCaseDescription": "javascript-void-operator-delete-test",
@@ -297,7 +297,7 @@
],
"patch": [
"diff --git a/void-operator.js b/void-operator.js",
- "index 738c34a..8e9ceba 100644",
+ "index 738c34a4..8e9ceba2 100644",
"--- a/void-operator.js",
"+++ b/void-operator.js",
"@@ -1,2 +1 @@",
@@ -305,7 +305,7 @@
" void c()"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "350bf156c704fb4f26d0ada86678e654d40d70cc..684600d4371b29448fa610da1a5e4d2d7710c3aa"
+ "shas": "8835bba7c5048d609d2eb5e67b0680423893ab3d..b67f11bb5940973edc50e68a156cae2f15578324"
}
,{
"testCaseDescription": "javascript-void-operator-delete-rest-test",
@@ -336,12 +336,12 @@
],
"patch": [
"diff --git a/void-operator.js b/void-operator.js",
- "index 8e9ceba..e69de29 100644",
+ "index 8e9ceba2..e69de29b 100644",
"--- a/void-operator.js",
"+++ b/void-operator.js",
"@@ -1 +0,0 @@",
"-void c()"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "684600d4371b29448fa610da1a5e4d2d7710c3aa..5da04c6d20aa6fdedbc205bf855829ccd10687f3"
+ "shas": "b67f11bb5940973edc50e68a156cae2f15578324..37c35686cb5d7f4301f701d97d4050125dffa916"
}]
diff --git a/test/corpus/diff-summaries/javascript/while-statement.json b/test/corpus/diff-summaries/javascript/while-statement.json
index 03a6ebc0f..853d2435b 100644
--- a/test/corpus/diff-summaries/javascript/while-statement.json
+++ b/test/corpus/diff-summaries/javascript/while-statement.json
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/while-statement.js b/while-statement.js",
- "index e69de29..1ea2800 100644",
+ "index e69de29b..1ea2800e 100644",
"--- a/while-statement.js",
"+++ b/while-statement.js",
"@@ -0,0 +1 @@",
"+while (a) { b(); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0b1a50d075cdb5202c523f929502c24a9fce63ce..db921ea9f999f72cb6399c64092e4b0904628ff8"
+ "shas": "0494efa588d0a283d42c62a35bcee1f439b6a16d..54ac72510f6e996e2b2b090f61e248ba73a5c2c5"
}
,{
"testCaseDescription": "javascript-while-statement-replacement-insert-test",
@@ -80,7 +80,7 @@
],
"patch": [
"diff --git a/while-statement.js b/while-statement.js",
- "index 1ea2800..c322323 100644",
+ "index 1ea2800e..c322323d 100644",
"--- a/while-statement.js",
"+++ b/while-statement.js",
"@@ -1 +1,3 @@",
@@ -89,7 +89,7 @@
" while (a) { b(); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "db921ea9f999f72cb6399c64092e4b0904628ff8..daa66677bfa5359e0679879da34e3ee1bed674a6"
+ "shas": "54ac72510f6e996e2b2b090f61e248ba73a5c2c5..800861d8d89a0e71e9b3001ad7153e0e601ab022"
}
,{
"testCaseDescription": "javascript-while-statement-delete-insert-test",
@@ -159,7 +159,7 @@
],
"patch": [
"diff --git a/while-statement.js b/while-statement.js",
- "index c322323..ea96716 100644",
+ "index c322323d..ea967164 100644",
"--- a/while-statement.js",
"+++ b/while-statement.js",
"@@ -1,3 +1,3 @@",
@@ -169,7 +169,7 @@
" while (a) { b(); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "daa66677bfa5359e0679879da34e3ee1bed674a6..24da8276225fa14bdffd90de951fc90cd18759ed"
+ "shas": "800861d8d89a0e71e9b3001ad7153e0e601ab022..e7d35e42f6fbcff10962e9f3706b4c2d364fbb45"
}
,{
"testCaseDescription": "javascript-while-statement-replacement-test",
@@ -239,7 +239,7 @@
],
"patch": [
"diff --git a/while-statement.js b/while-statement.js",
- "index ea96716..c322323 100644",
+ "index ea967164..c322323d 100644",
"--- a/while-statement.js",
"+++ b/while-statement.js",
"@@ -1,3 +1,3 @@",
@@ -249,7 +249,7 @@
" while (a) { b(); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "24da8276225fa14bdffd90de951fc90cd18759ed..cae263f93a9ddcbed5411b06251f41d4da9c07d4"
+ "shas": "e7d35e42f6fbcff10962e9f3706b4c2d364fbb45..c85f24d68fd3b3b390439f71aa7974964a6a3ede"
}
,{
"testCaseDescription": "javascript-while-statement-delete-replacement-test",
@@ -310,7 +310,7 @@
],
"patch": [
"diff --git a/while-statement.js b/while-statement.js",
- "index c322323..28f4b21 100644",
+ "index c322323d..28f4b210 100644",
"--- a/while-statement.js",
"+++ b/while-statement.js",
"@@ -1,3 +1,2 @@",
@@ -320,7 +320,7 @@
"+while (b) { a(); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "cae263f93a9ddcbed5411b06251f41d4da9c07d4..09f8c3d79b360939277158f185f0e13ecbecdd11"
+ "shas": "c85f24d68fd3b3b390439f71aa7974964a6a3ede..b68df7e7afa74cc4ad640cbf6cae14983242c61d"
}
,{
"testCaseDescription": "javascript-while-statement-delete-test",
@@ -351,7 +351,7 @@
],
"patch": [
"diff --git a/while-statement.js b/while-statement.js",
- "index 28f4b21..e185b25 100644",
+ "index 28f4b210..e185b25d 100644",
"--- a/while-statement.js",
"+++ b/while-statement.js",
"@@ -1,2 +1 @@",
@@ -359,7 +359,7 @@
" while (b) { a(); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "09f8c3d79b360939277158f185f0e13ecbecdd11..11144cc015f5698c8473a6efd76c3129422cf2a2"
+ "shas": "b68df7e7afa74cc4ad640cbf6cae14983242c61d..cf930c906150e222d831b17a0c6f28f7d5879167"
}
,{
"testCaseDescription": "javascript-while-statement-delete-rest-test",
@@ -390,12 +390,12 @@
],
"patch": [
"diff --git a/while-statement.js b/while-statement.js",
- "index e185b25..e69de29 100644",
+ "index e185b25d..e69de29b 100644",
"--- a/while-statement.js",
"+++ b/while-statement.js",
"@@ -1 +0,0 @@",
"-while (b) { a(); };"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "11144cc015f5698c8473a6efd76c3129422cf2a2..cd322134775da8db98f5a151ec8e2f5d9eddd3cf"
+ "shas": "cf930c906150e222d831b17a0c6f28f7d5879167..34742f99e05bf8c6402929d23886b55c725e282e"
}]
diff --git a/test/corpus/diff-summaries/javascript/yield.json b/test/corpus/diff-summaries/javascript/yield.json
index 6fbeade8d..c0a811322 100644
--- a/test/corpus/diff-summaries/javascript/yield.json
+++ b/test/corpus/diff-summaries/javascript/yield.json
@@ -34,7 +34,7 @@
"+function* foo(){ var index = 0; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "5c6bdce8f72c2d775feff2e1e2bafd6639ec3092..af359d80f0450c0c2196373f3a6135ad69d15448"
+ "shas": "5e76eb9bd80785120da1d03a39846954694b0a87..f57697ec59783c8e1203e436eae89fbebef52f08"
}
,{
"testCaseDescription": "javascript-yield-insert-test",
@@ -73,7 +73,7 @@
"+function* foo(){ var index = 0; yield i; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "af359d80f0450c0c2196373f3a6135ad69d15448..994d3630d7493bcd3de8987ef154ab8791944584"
+ "shas": "f57697ec59783c8e1203e436eae89fbebef52f08..56f91ef1d43bb39bcdf93188575968e3b886b851"
}
,{
"testCaseDescription": "javascript-yield-replacement-test",
@@ -124,7 +124,7 @@
"+function* foo(){ var index = 0; yield i++; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "994d3630d7493bcd3de8987ef154ab8791944584..04b9b20aaf2b5f555b5223dfba6c303f01450f5e"
+ "shas": "56f91ef1d43bb39bcdf93188575968e3b886b851..f949be3ba0a2939702be6eda4eb8810b35b3240a"
}
,{
"testCaseDescription": "javascript-yield-delete-replacement-test",
@@ -175,7 +175,7 @@
"+function* foo(){ var index = 0; yield i; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "04b9b20aaf2b5f555b5223dfba6c303f01450f5e..0f042b1a2b628149d5fe3d38ac22ddb0b1e1fd4a"
+ "shas": "f949be3ba0a2939702be6eda4eb8810b35b3240a..0893b0411a64cf78f313d02dd09aaf0d21287d61"
}
,{
"testCaseDescription": "javascript-yield-delete-insert-test",
@@ -214,7 +214,7 @@
"+function* foo(){ var index = 0; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "0f042b1a2b628149d5fe3d38ac22ddb0b1e1fd4a..2bb888580d4105d265e9137474d813ab92ce6359"
+ "shas": "0893b0411a64cf78f313d02dd09aaf0d21287d61..de14a8652b0a678eb5f0bcbe9936d5fe4aa4d31f"
}
,{
"testCaseDescription": "javascript-yield-teardown-test",
@@ -252,5 +252,5 @@
"-function* foo(){ var index = 0; }"
],
"gitDir": "test/corpus/repos/javascript",
- "shas": "2bb888580d4105d265e9137474d813ab92ce6359..0e81c586bea55e0eeb46e3422b25ccba96c7d9ea"
+ "shas": "de14a8652b0a678eb5f0bcbe9936d5fe4aa4d31f..abce7caf7e67e197076f10ee997f4a8e08480f93"
}]
diff --git a/test/corpus/diff-summaries/ruby/and-or.json b/test/corpus/diff-summaries/ruby/and-or.json
index 2494e320d..39e50bd6c 100644
--- a/test/corpus/diff-summaries/ruby/and-or.json
+++ b/test/corpus/diff-summaries/ruby/and-or.json
@@ -34,7 +34,7 @@
"+foo and bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "760d160893f207bd4480bd4cdbf9225479c045c8..7cc07c9bd56c68a9fd52504dc6c34e6097472cc7"
+ "shas": "205ba4865cabb2363522ff4a941ac640364c78b9..58d9620982ce5420b8786bf5b7f24a4fccf17840"
}
,{
"testCaseDescription": "ruby-and-or-replacement-insert-test",
@@ -105,7 +105,7 @@
" foo and bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7cc07c9bd56c68a9fd52504dc6c34e6097472cc7..8f8ad308a601afec6fedb6a643c43f402355bc47"
+ "shas": "58d9620982ce5420b8786bf5b7f24a4fccf17840..fdacc6d2adffabae4549c817a7b5e1ac1410ad14"
}
,{
"testCaseDescription": "ruby-and-or-delete-insert-test",
@@ -174,7 +174,7 @@
" foo and bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8f8ad308a601afec6fedb6a643c43f402355bc47..6fd584c9522117801bb5565763f5b16c9148d89c"
+ "shas": "fdacc6d2adffabae4549c817a7b5e1ac1410ad14..12bb9bd7d73b5853376d23065d453b1319acded1"
}
,{
"testCaseDescription": "ruby-and-or-replacement-test",
@@ -243,7 +243,7 @@
" foo and bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6fd584c9522117801bb5565763f5b16c9148d89c..85540cf719adb2e06da1aaa2bdf7d65020cbafa0"
+ "shas": "12bb9bd7d73b5853376d23065d453b1319acded1..b987241766c0074489dd821be6a10b0f94ba4664"
}
,{
"testCaseDescription": "ruby-and-or-delete-replacement-test",
@@ -285,7 +285,7 @@
"-foo and bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "85540cf719adb2e06da1aaa2bdf7d65020cbafa0..ab50c272197758505577449e768972f0cdd5eb59"
+ "shas": "b987241766c0074489dd821be6a10b0f94ba4664..421da0092d201b7de942559a2a44c9e82ad6f074"
}
,{
"testCaseDescription": "ruby-and-or-delete-test",
@@ -325,7 +325,7 @@
" a or b and c"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ab50c272197758505577449e768972f0cdd5eb59..749204b420120020a89e45437c441208244effde"
+ "shas": "421da0092d201b7de942559a2a44c9e82ad6f074..01935816ce300d461104509bcbe0a91e61c57484"
}
,{
"testCaseDescription": "ruby-and-or-delete-rest-test",
@@ -379,5 +379,5 @@
"-a or b and c"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "749204b420120020a89e45437c441208244effde..276112ad3f93ee93fa30985c16b91d38d36f4e32"
+ "shas": "01935816ce300d461104509bcbe0a91e61c57484..72d6e4e549ce17f88e6130002ccc0ecd6302fdf2"
}]
diff --git a/test/corpus/diff-summaries/ruby/array.json b/test/corpus/diff-summaries/ruby/array.json
index 78bf842ad..b802a5682 100644
--- a/test/corpus/diff-summaries/ruby/array.json
+++ b/test/corpus/diff-summaries/ruby/array.json
@@ -34,7 +34,7 @@
"+[ 1, 2, 3]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c05b5a765cdcea2458b77acf718ccf2623e578fa..ca3a45216df04fc19cebe9e7c364f2030f022743"
+ "shas": "38a4fc97908a2d22a188038b11a90fee2a3326eb..04d06d6eb3c7bc7ba3bccffe71c5d733d3dcea5b"
}
,{
"testCaseDescription": "ruby-array-replacement-insert-test",
@@ -89,7 +89,7 @@
" [ 1, 2, 3]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ca3a45216df04fc19cebe9e7c364f2030f022743..d137cd075643c5f353f52bdab672a8fea7cde729"
+ "shas": "04d06d6eb3c7bc7ba3bccffe71c5d733d3dcea5b..cbc918613a1b1ce16ffc4cb0f5704e545ce31950"
}
,{
"testCaseDescription": "ruby-array-delete-insert-test",
@@ -205,7 +205,7 @@
" [ 1, 2, 3]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d137cd075643c5f353f52bdab672a8fea7cde729..e363bd7e7c5b9226206a1bc5c524b0043699c1af"
+ "shas": "cbc918613a1b1ce16ffc4cb0f5704e545ce31950..4e4648cbfae5013b4e7ce9b6b9cec267191f0e83"
}
,{
"testCaseDescription": "ruby-array-replacement-test",
@@ -321,7 +321,7 @@
" [ 1, 2, 3]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e363bd7e7c5b9226206a1bc5c524b0043699c1af..c25ee7443537fec8ed353826a56bca4112f68f29"
+ "shas": "4e4648cbfae5013b4e7ce9b6b9cec267191f0e83..b6776657e0e9d69a5ceab8562d2eeb1d2d05f363"
}
,{
"testCaseDescription": "ruby-array-delete-replacement-test",
@@ -392,7 +392,7 @@
"+['a', 'b', 'c']"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c25ee7443537fec8ed353826a56bca4112f68f29..bba78842632a40b370c116455d6cf638872706fd"
+ "shas": "b6776657e0e9d69a5ceab8562d2eeb1d2d05f363..fdf541be36fad746c379c5243c1d2130cabec95b"
}
,{
"testCaseDescription": "ruby-array-delete-test",
@@ -431,7 +431,7 @@
" ['a', 'b', 'c']"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "bba78842632a40b370c116455d6cf638872706fd..71c9788146d44a877852a5a0b8340c540f967d70"
+ "shas": "fdf541be36fad746c379c5243c1d2130cabec95b..e4cdc99a837f1b447ecd5e5b2ace5b6f1878b1b5"
}
,{
"testCaseDescription": "ruby-array-delete-rest-test",
@@ -469,5 +469,5 @@
"-['a', 'b', 'c']"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "71c9788146d44a877852a5a0b8340c540f967d70..793e1bdbe7ec874e9b83489ff39233476953a8f8"
+ "shas": "e4cdc99a837f1b447ecd5e5b2ace5b6f1878b1b5..50239ae63445ee12774182b323b735f392bdacdf"
}]
diff --git a/test/corpus/diff-summaries/ruby/assignment.json b/test/corpus/diff-summaries/ruby/assignment.json
index 96e04ed51..83883957f 100644
--- a/test/corpus/diff-summaries/ruby/assignment.json
+++ b/test/corpus/diff-summaries/ruby/assignment.json
@@ -34,7 +34,7 @@
"+x = 0"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "62316f48f883c9c707459bcdd67ebcae15a231a8..939f7f330ea326f64067f76a43d129b407516427"
+ "shas": "97513ccc92beee8dc279d44117dce9155e578efe..0bfb74457a0fd6be8afb191deee0bad948bf0492"
}
,{
"testCaseDescription": "ruby-assignment-replacement-insert-test",
@@ -89,7 +89,7 @@
" x = 0"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "939f7f330ea326f64067f76a43d129b407516427..d13c7ef06478483af7b33662309f8a8ac7531259"
+ "shas": "0bfb74457a0fd6be8afb191deee0bad948bf0492..0485661f12dbf56cc0ead739ea960f9a5cd02b12"
}
,{
"testCaseDescription": "ruby-assignment-delete-insert-test",
@@ -142,7 +142,7 @@
" x = 0"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d13c7ef06478483af7b33662309f8a8ac7531259..e6c370c9c3373f9585167e27a117b1c458f1f703"
+ "shas": "0485661f12dbf56cc0ead739ea960f9a5cd02b12..70d038e09bfc550c0ea49a8d6efd4a5933fbb067"
}
,{
"testCaseDescription": "ruby-assignment-replacement-test",
@@ -195,7 +195,7 @@
" x = 0"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e6c370c9c3373f9585167e27a117b1c458f1f703..a936b4450f977ef078cc2de08838b88e4b96cdfc"
+ "shas": "70d038e09bfc550c0ea49a8d6efd4a5933fbb067..1e0fca806d879ae446160274b0e11986f2698e8e"
}
,{
"testCaseDescription": "ruby-assignment-delete-replacement-test",
@@ -266,7 +266,7 @@
"+x = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a936b4450f977ef078cc2de08838b88e4b96cdfc..b90c9ecb1cbb7d92c59ef6f9abe73a1b609f237b"
+ "shas": "1e0fca806d879ae446160274b0e11986f2698e8e..5b67a5140d66ec47b6fc638e8d424f45a14b2036"
}
,{
"testCaseDescription": "ruby-assignment-delete-test",
@@ -305,7 +305,7 @@
" x = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b90c9ecb1cbb7d92c59ef6f9abe73a1b609f237b..44af27381c5212148bd76e27261e7aa7de1b67c7"
+ "shas": "5b67a5140d66ec47b6fc638e8d424f45a14b2036..ae1319ca3c7aef18c9fba00864fe36a3d7338044"
}
,{
"testCaseDescription": "ruby-assignment-delete-rest-test",
@@ -343,5 +343,5 @@
"-x = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "44af27381c5212148bd76e27261e7aa7de1b67c7..581df677d2a670ad93b167b548320511297d8332"
+ "shas": "ae1319ca3c7aef18c9fba00864fe36a3d7338044..7eeecdbb471963b09ff71e25f66b66ce9b2b9141"
}]
diff --git a/test/corpus/diff-summaries/ruby/begin-block.json b/test/corpus/diff-summaries/ruby/begin-block.json
index 6e77b09fb..d7770a5b6 100644
--- a/test/corpus/diff-summaries/ruby/begin-block.json
+++ b/test/corpus/diff-summaries/ruby/begin-block.json
@@ -36,7 +36,7 @@
"+}"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "585af1aa8a79718f22dd0fe0f8ac3051cfc56a4f..1f9ce3015ba7885c7ff5acb7420e9d240cb2ea5f"
+ "shas": "13b54918666502353431828fabfae483e79016f6..ab95dd845e232d1b15d0a9159ba71ea967234cdd"
}
,{
"testCaseDescription": "ruby-begin-block-replacement-insert-test",
@@ -113,7 +113,7 @@
" }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1f9ce3015ba7885c7ff5acb7420e9d240cb2ea5f..60e77aa00dcbc7a636fd7749ad8be756d41bfe0f"
+ "shas": "ab95dd845e232d1b15d0a9159ba71ea967234cdd..768468aad577e2ca1c37ef0e85402e55c5df1e80"
}
,{
"testCaseDescription": "ruby-begin-block-delete-insert-test",
@@ -187,7 +187,7 @@
" foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "60e77aa00dcbc7a636fd7749ad8be756d41bfe0f..207946457ef222ec733ff1e0ce48dfd326fc3449"
+ "shas": "768468aad577e2ca1c37ef0e85402e55c5df1e80..dd09bb810f4aaf44d62808213d5e82a4e193ee1c"
}
,{
"testCaseDescription": "ruby-begin-block-replacement-test",
@@ -258,7 +258,7 @@
" foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "207946457ef222ec733ff1e0ce48dfd326fc3449..0a57164a8ecbfcf9d9390b1d4f9db9db7afae84b"
+ "shas": "dd09bb810f4aaf44d62808213d5e82a4e193ee1c..8fcb3cb05329b9961aa6fd2080e4220cb1a6f2c4"
}
,{
"testCaseDescription": "ruby-begin-block-delete-replacement-test",
@@ -307,7 +307,7 @@
" }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0a57164a8ecbfcf9d9390b1d4f9db9db7afae84b..8ce48cf274a6211aed53733945c0c9e3c3f08464"
+ "shas": "8fcb3cb05329b9961aa6fd2080e4220cb1a6f2c4..e45ce4f47febb1c4536cb1e67b0e77e2601fac8d"
}
,{
"testCaseDescription": "ruby-begin-block-delete-test",
@@ -350,7 +350,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8ce48cf274a6211aed53733945c0c9e3c3f08464..d00df464924d84f60bdd896dad98c5b4af90e5d6"
+ "shas": "e45ce4f47febb1c4536cb1e67b0e77e2601fac8d..14f3d6830d0de89b6d473bdfb743645a794b25e3"
}
,{
"testCaseDescription": "ruby-begin-block-delete-rest-test",
@@ -406,5 +406,5 @@
"-}"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d00df464924d84f60bdd896dad98c5b4af90e5d6..bc59f083f15dede23c12c1777479b8f0ea372aaa"
+ "shas": "14f3d6830d0de89b6d473bdfb743645a794b25e3..51638d239b4fc813f309e3143df19945f9134fc9"
}]
diff --git a/test/corpus/diff-summaries/ruby/begin.json b/test/corpus/diff-summaries/ruby/begin.json
index 65d3a5062..39d14d6f2 100644
--- a/test/corpus/diff-summaries/ruby/begin.json
+++ b/test/corpus/diff-summaries/ruby/begin.json
@@ -35,7 +35,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "166c92e7981b72600fa1e5096d0be628cc8d962c..41b6eb375409c26233ff4c19111e4760bd063764"
+ "shas": "a07975f1b55276cfbfa8bc5865e2ad77f0b12b14..b45a91ba70b663823b8bdf8355ba224c1a28fedf"
}
,{
"testCaseDescription": "ruby-begin-insert-test",
@@ -76,7 +76,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "41b6eb375409c26233ff4c19111e4760bd063764..c348ec57e45ce7f68b908fd7298c56674e54714b"
+ "shas": "b45a91ba70b663823b8bdf8355ba224c1a28fedf..6cc5c375ce8ef2281d0145fd30d98853ec2e4243"
}
,{
"testCaseDescription": "ruby-begin-replacement-test",
@@ -118,7 +118,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c348ec57e45ce7f68b908fd7298c56674e54714b..0ecb1ca4e9d2860498ed4f4a8f28f85bbd7cbc75"
+ "shas": "6cc5c375ce8ef2281d0145fd30d98853ec2e4243..6733a6b5739f525c89ca78a9dd4cd12b433e2be5"
}
,{
"testCaseDescription": "ruby-begin-delete-replacement-test",
@@ -160,7 +160,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0ecb1ca4e9d2860498ed4f4a8f28f85bbd7cbc75..d762f1123fa8127435ea014647e7d06cde5b7ba9"
+ "shas": "6733a6b5739f525c89ca78a9dd4cd12b433e2be5..ca868f9c201ba09a26e52911b44fbb736967ad41"
}
,{
"testCaseDescription": "ruby-begin-delete-insert-test",
@@ -201,7 +201,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d762f1123fa8127435ea014647e7d06cde5b7ba9..7d7d7f470bf35e7bfe2745ff858c712ac806808f"
+ "shas": "ca868f9c201ba09a26e52911b44fbb736967ad41..ca4370ab650947bec3b6dd4b4ebda89c4da4b8b3"
}
,{
"testCaseDescription": "ruby-begin-teardown-test",
@@ -240,5 +240,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7d7d7f470bf35e7bfe2745ff858c712ac806808f..5127fe99b505deff8beb2b738a1225eaaaee825f"
+ "shas": "ca4370ab650947bec3b6dd4b4ebda89c4da4b8b3..a60c38ac8820bc400cce7a8a87001d1c9b8889ff"
}]
diff --git a/test/corpus/diff-summaries/ruby/bitwise-operator.json b/test/corpus/diff-summaries/ruby/bitwise-operator.json
index fabf1b9e4..621bc822c 100644
--- a/test/corpus/diff-summaries/ruby/bitwise-operator.json
+++ b/test/corpus/diff-summaries/ruby/bitwise-operator.json
@@ -66,7 +66,7 @@
"+a ^ b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b8665811d4bea5d475c83e70b2b135910cd12238..51050871556d52452a2782271ef63e8f550c89ee"
+ "shas": "2078d66c2f08ace20a94d37cb9f7db8d7230f4da..d43938b02b213bfc58c7bcd4b26f26fd9f3b15b1"
}
,{
"testCaseDescription": "ruby-bitwise-operator-replacement-insert-test",
@@ -171,7 +171,7 @@
" a ^ b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "51050871556d52452a2782271ef63e8f550c89ee..525c2ebbda4beec1568f6c63bcbc039015272f9b"
+ "shas": "d43938b02b213bfc58c7bcd4b26f26fd9f3b15b1..15c849e1c8a2c17f5de6c0755fa374277de4b700"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-insert-test",
@@ -270,7 +270,7 @@
" a ^ b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "525c2ebbda4beec1568f6c63bcbc039015272f9b..3f3039307a83f40f2d42d81ed6c23af08b7af6b6"
+ "shas": "15c849e1c8a2c17f5de6c0755fa374277de4b700..899088409fd476d0b9915cf4010745662fe6ba48"
}
,{
"testCaseDescription": "ruby-bitwise-operator-replacement-test",
@@ -372,7 +372,7 @@
" a ^ b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3f3039307a83f40f2d42d81ed6c23af08b7af6b6..42f190c590146436dafef1e62eb0fe176434c551"
+ "shas": "899088409fd476d0b9915cf4010745662fe6ba48..a1b2ae060e5810c03411b779be39e93a3ceff844"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-replacement-test",
@@ -509,7 +509,7 @@
"+a << b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "42f190c590146436dafef1e62eb0fe176434c551..3276a2e36bef341d0571c6814b76584a31bac5ee"
+ "shas": "a1b2ae060e5810c03411b779be39e93a3ceff844..c5f974897630d13fc61e69fc2fd9b86bd3ad39f9"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-test",
@@ -581,7 +581,7 @@
" a << b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3276a2e36bef341d0571c6814b76584a31bac5ee..5cfff4f62af8d8b7539061860316be445ccf73b8"
+ "shas": "c5f974897630d13fc61e69fc2fd9b86bd3ad39f9..a2cd2bbf396cf38588f8550d29335b604c08d4e5"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-rest-test",
@@ -635,5 +635,5 @@
"-a << b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5cfff4f62af8d8b7539061860316be445ccf73b8..c68e6c55ea690a0be0abc87e1c88965206d29d27"
+ "shas": "a2cd2bbf396cf38588f8550d29335b604c08d4e5..45978cfdd439c3dd5f0de02209a46608459cf93f"
}]
diff --git a/test/corpus/diff-summaries/ruby/boolean-operator.json b/test/corpus/diff-summaries/ruby/boolean-operator.json
index aeeb4865f..1e10391c4 100644
--- a/test/corpus/diff-summaries/ruby/boolean-operator.json
+++ b/test/corpus/diff-summaries/ruby/boolean-operator.json
@@ -34,7 +34,7 @@
"+a || b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2412502f463a0cb9416638cc2da07ab2d024a52f..4329bba0adf3fda4dcf3a4495f2dcd94589d8daf"
+ "shas": "502a790cb75c5cd2f5a1166305c358bca7535c16..0c26fdb0f1aba41228b41822641f41c7cf33e3ff"
}
,{
"testCaseDescription": "ruby-boolean-operator-replacement-insert-test",
@@ -89,7 +89,7 @@
" a || b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4329bba0adf3fda4dcf3a4495f2dcd94589d8daf..bc78661788a1988b9f04b3d8099943d40ccb6f1d"
+ "shas": "0c26fdb0f1aba41228b41822641f41c7cf33e3ff..bce58fa8f6e6b6a1637bed891e3f9be91cba8614"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-insert-test",
@@ -142,7 +142,7 @@
" a || b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "bc78661788a1988b9f04b3d8099943d40ccb6f1d..95eeb1dcc932d29956c3fc936ebc8df95b71d852"
+ "shas": "bce58fa8f6e6b6a1637bed891e3f9be91cba8614..b07b94c6b0a2f2bb84788f610181a7a5989fb404"
}
,{
"testCaseDescription": "ruby-boolean-operator-replacement-test",
@@ -195,7 +195,7 @@
" a || b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "95eeb1dcc932d29956c3fc936ebc8df95b71d852..4f08052b96e11f4c14730747195c1c92f2c7959d"
+ "shas": "b07b94c6b0a2f2bb84788f610181a7a5989fb404..d3ed9391e469db052979ba6991b101b7a1baa97b"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-replacement-test",
@@ -266,7 +266,7 @@
"+a && b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4f08052b96e11f4c14730747195c1c92f2c7959d..baa0ce006152364fbccfc7f655e05adb539da733"
+ "shas": "d3ed9391e469db052979ba6991b101b7a1baa97b..d97528c4c6f6b944d5415386ed8c94784c3d5cad"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-test",
@@ -305,7 +305,7 @@
" a && b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "baa0ce006152364fbccfc7f655e05adb539da733..3a167415bc59515ec82cb809b236ca334af70bcd"
+ "shas": "d97528c4c6f6b944d5415386ed8c94784c3d5cad..20168e6d538da9ab68d624225cb4321da06adf13"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-rest-test",
@@ -343,5 +343,5 @@
"-a && b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3a167415bc59515ec82cb809b236ca334af70bcd..5a6d083875f84d691932dcce0fc121fdc3a56264"
+ "shas": "20168e6d538da9ab68d624225cb4321da06adf13..6c27e99fb23d5f85525e0885c8e8a54cbfc8717a"
}]
diff --git a/test/corpus/diff-summaries/ruby/class.json b/test/corpus/diff-summaries/ruby/class.json
index 4e01e67d0..a816b0a44 100644
--- a/test/corpus/diff-summaries/ruby/class.json
+++ b/test/corpus/diff-summaries/ruby/class.json
@@ -36,7 +36,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ebc16e531db91e278be158e0331d53d4662ad941..5e2215181b0d458b246a17cfcff87a83a93bdf8b"
+ "shas": "ef10a31e176341061b8156a6bf867297521bb536..79e16992eab7cf2d4cedd100061c460e6cdf1717"
}
,{
"testCaseDescription": "ruby-class-replacement-insert-test",
@@ -97,7 +97,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5e2215181b0d458b246a17cfcff87a83a93bdf8b..1bafee2d2f36e4b9cd366c17b0980518c1fbf89a"
+ "shas": "79e16992eab7cf2d4cedd100061c460e6cdf1717..9641b02f32f40b7769e34cf24fab1f76e3ea13f0"
}
,{
"testCaseDescription": "ruby-class-delete-insert-test",
@@ -139,7 +139,7 @@
" class Foo < Super"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1bafee2d2f36e4b9cd366c17b0980518c1fbf89a..eac31bbf2f3921384eb5ace16b975e0d19bec71f"
+ "shas": "9641b02f32f40b7769e34cf24fab1f76e3ea13f0..d30f11a12e5a17368e7e87ce6c336d7360f4a1e1"
}
,{
"testCaseDescription": "ruby-class-replacement-test",
@@ -181,7 +181,7 @@
" class Foo < Super"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "eac31bbf2f3921384eb5ace16b975e0d19bec71f..cbf40bb9582a34c3d040e59287a0f68657389ed4"
+ "shas": "d30f11a12e5a17368e7e87ce6c336d7360f4a1e1..c99112cf6f4c6a1d6c7d460214f7fb6fba19eb9a"
}
,{
"testCaseDescription": "ruby-class-delete-replacement-test",
@@ -258,7 +258,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cbf40bb9582a34c3d040e59287a0f68657389ed4..c44c459ce8d0efcc395bca51374a645977ca9b9c"
+ "shas": "c99112cf6f4c6a1d6c7d460214f7fb6fba19eb9a..49a6b1242040780132125b4f732af36832c06af4"
}
,{
"testCaseDescription": "ruby-class-delete-test",
@@ -301,7 +301,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c44c459ce8d0efcc395bca51374a645977ca9b9c..1adb2921e5326d0bfc0171d779ed83cf62da6a70"
+ "shas": "49a6b1242040780132125b4f732af36832c06af4..5cfa249fdd5d285983923048a490943c438a0bce"
}
,{
"testCaseDescription": "ruby-class-delete-rest-test",
@@ -341,5 +341,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1adb2921e5326d0bfc0171d779ed83cf62da6a70..ab126516af689f66354c40e2b73bad9ea5b34fc4"
+ "shas": "5cfa249fdd5d285983923048a490943c438a0bce..0e65da6c947e134d3e5cd0b5f20b813dd2fc367b"
}]
diff --git a/test/corpus/diff-summaries/ruby/comment.json b/test/corpus/diff-summaries/ruby/comment.json
index e193d31d4..e2b247da3 100644
--- a/test/corpus/diff-summaries/ruby/comment.json
+++ b/test/corpus/diff-summaries/ruby/comment.json
@@ -16,7 +16,7 @@
"+# This is a comment"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "581df677d2a670ad93b167b548320511297d8332..4d101d0c1e5d133362d2e51384526bc842090237"
+ "shas": "7eeecdbb471963b09ff71e25f66b66ce9b2b9141..b0427de530f6124c865e505a44754a4aac6d3c10"
}
,{
"testCaseDescription": "ruby-comment-replacement-insert-test",
@@ -41,7 +41,7 @@
" # This is a comment"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4d101d0c1e5d133362d2e51384526bc842090237..82844d01f5488e372a03c1775bfe067b4863236d"
+ "shas": "b0427de530f6124c865e505a44754a4aac6d3c10..98bd2631916190437a03c7742b88ef8ec86f4adc"
}
,{
"testCaseDescription": "ruby-comment-delete-insert-test",
@@ -67,7 +67,7 @@
" # This is a comment"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "82844d01f5488e372a03c1775bfe067b4863236d..480511f95251c93ca3ce1e177a0a9e5a44393e5c"
+ "shas": "98bd2631916190437a03c7742b88ef8ec86f4adc..450a24b900ec9513a156d85cdb5b7b4c5cab43b4"
}
,{
"testCaseDescription": "ruby-comment-replacement-test",
@@ -93,7 +93,7 @@
" # This is a comment"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "480511f95251c93ca3ce1e177a0a9e5a44393e5c..6f19900e698110e71395e3df1d6295125e6a296c"
+ "shas": "450a24b900ec9513a156d85cdb5b7b4c5cab43b4..200a2471e3250c1e61b96f650e8ed0fe47ee4edf"
}
,{
"testCaseDescription": "ruby-comment-delete-replacement-test",
@@ -119,7 +119,7 @@
"-# This is a comment"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6f19900e698110e71395e3df1d6295125e6a296c..7d9ba1287f69442902c32989c9b412faeef252ac"
+ "shas": "200a2471e3250c1e61b96f650e8ed0fe47ee4edf..2604488d2845e68dac3cd479af42be24ab86af66"
}
,{
"testCaseDescription": "ruby-comment-delete-test",
@@ -142,7 +142,7 @@
" comment"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7d9ba1287f69442902c32989c9b412faeef252ac..f917235ee71bd1e20bb860ded0c031801957680a"
+ "shas": "2604488d2845e68dac3cd479af42be24ab86af66..df7edd9565f1c770a622ed1d77a214c8fa957651"
}
,{
"testCaseDescription": "ruby-comment-delete-rest-test",
@@ -165,5 +165,5 @@
"-=end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f917235ee71bd1e20bb860ded0c031801957680a..102ebf0b263b96260e08b9e01bc647378aac78db"
+ "shas": "df7edd9565f1c770a622ed1d77a214c8fa957651..3345b250a3b074d0b3725cfa9ada030ac0733c03"
}]
diff --git a/test/corpus/diff-summaries/ruby/comparision-operator.json b/test/corpus/diff-summaries/ruby/comparision-operator.json
index 20149bc26..3aa607cb5 100644
--- a/test/corpus/diff-summaries/ruby/comparision-operator.json
+++ b/test/corpus/diff-summaries/ruby/comparision-operator.json
@@ -50,7 +50,7 @@
"+a > b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8b0ce2b5b84158c85e605ab2a0073b9b89994fed..11eb32a836c6ff108d2a9f246162212ec6405922"
+ "shas": "1b803e056a1487ac155e74204ddaa92b7fd30c5b..52cc2f5a6aa5de8de8a79280b0f2377947e2cb24"
}
,{
"testCaseDescription": "ruby-comparision-operator-replacement-insert-test",
@@ -138,7 +138,7 @@
" a > b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "11eb32a836c6ff108d2a9f246162212ec6405922..a245a3c38eaaf69df059ac9daf8d73b5c6db4057"
+ "shas": "52cc2f5a6aa5de8de8a79280b0f2377947e2cb24..8099204a2c18280356a36fe06a8b992bbd38fc42"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-insert-test",
@@ -221,7 +221,7 @@
" x < y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a245a3c38eaaf69df059ac9daf8d73b5c6db4057..329a56f174b99e19ec8ef294cbf3466d6f169cd8"
+ "shas": "8099204a2c18280356a36fe06a8b992bbd38fc42..6accee55dd132f8a6a0b1a3af69c6472583688d8"
}
,{
"testCaseDescription": "ruby-comparision-operator-replacement-test",
@@ -304,7 +304,7 @@
" x < y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "329a56f174b99e19ec8ef294cbf3466d6f169cd8..301792012e4b641a97cfe53ac89611486e08f10f"
+ "shas": "6accee55dd132f8a6a0b1a3af69c6472583688d8..3f28fafed22fa1395802a60d38d0b344bd1aac41"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-replacement-test",
@@ -424,7 +424,7 @@
"+a >= b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "301792012e4b641a97cfe53ac89611486e08f10f..8e9fd0197af847d0b52fef431f4bb1558a2c3a97"
+ "shas": "3f28fafed22fa1395802a60d38d0b344bd1aac41..d2004b731d8dde2547f73bb629984bffd73202cc"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-test",
@@ -480,7 +480,7 @@
" a >= b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8e9fd0197af847d0b52fef431f4bb1558a2c3a97..7422e633ba92a94f164c43bfc80ec14920ab2153"
+ "shas": "d2004b731d8dde2547f73bb629984bffd73202cc..e43586a99445693683289cacdfa6cb1a08a9a3d6"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-rest-test",
@@ -534,5 +534,5 @@
"-a >= b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7422e633ba92a94f164c43bfc80ec14920ab2153..b8665811d4bea5d475c83e70b2b135910cd12238"
+ "shas": "e43586a99445693683289cacdfa6cb1a08a9a3d6..2078d66c2f08ace20a94d37cb9f7db8d7230f4da"
}]
diff --git a/test/corpus/diff-summaries/ruby/conditional-assignment.json b/test/corpus/diff-summaries/ruby/conditional-assignment.json
index d98a99704..adcd240fa 100644
--- a/test/corpus/diff-summaries/ruby/conditional-assignment.json
+++ b/test/corpus/diff-summaries/ruby/conditional-assignment.json
@@ -34,7 +34,7 @@
"+x ||= 5"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7c923dd9edc785cfae17ddf168ca4f063c7e7604..fec1351ff34382c4388b4190c133ed0bf2447166"
+ "shas": "050c435fbd32f39fd591765021defb50b60b0d2a..ba621677eb5c3f81243fb8d796cf8b4eafd240a8"
}
,{
"testCaseDescription": "ruby-conditional-assignment-replacement-insert-test",
@@ -89,7 +89,7 @@
" x ||= 5"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fec1351ff34382c4388b4190c133ed0bf2447166..557d343ef0d8d55d28cc377aafebfa30c77c2c62"
+ "shas": "ba621677eb5c3f81243fb8d796cf8b4eafd240a8..893895fcc912d84499e0b9e8b1a860915a7a9086"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-insert-test",
@@ -142,7 +142,7 @@
" x ||= 5"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "557d343ef0d8d55d28cc377aafebfa30c77c2c62..e16d621420a3602f2d60875df77a3b6b9d0bb6c9"
+ "shas": "893895fcc912d84499e0b9e8b1a860915a7a9086..131ed61615b3888b89e8eaeca24716c140cdcd5c"
}
,{
"testCaseDescription": "ruby-conditional-assignment-replacement-test",
@@ -195,7 +195,7 @@
" x ||= 5"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e16d621420a3602f2d60875df77a3b6b9d0bb6c9..c27b7c722bb192102922964a90ca12da98eadb08"
+ "shas": "131ed61615b3888b89e8eaeca24716c140cdcd5c..dba7279b4c585953915103b661f5d69c5c9e8b72"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-replacement-test",
@@ -266,7 +266,7 @@
"+x &&= 7"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c27b7c722bb192102922964a90ca12da98eadb08..539e9e8cad37b9c6152c61f8a4ca3375021f2a56"
+ "shas": "dba7279b4c585953915103b661f5d69c5c9e8b72..aaab18417cba23f1aa49d8eb95a5de80e9c7e3ae"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-test",
@@ -305,7 +305,7 @@
" x &&= 7"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "539e9e8cad37b9c6152c61f8a4ca3375021f2a56..481e8df80d47fd0a2530b869ee0fa0e07db6ad04"
+ "shas": "aaab18417cba23f1aa49d8eb95a5de80e9c7e3ae..10aa5b9b4ea072110591f44de91ad83bcadcde92"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-rest-test",
@@ -343,5 +343,5 @@
"-x &&= 7"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "481e8df80d47fd0a2530b869ee0fa0e07db6ad04..f6e95f576fdbe837a5fa09bd74b0d87bcca7c856"
+ "shas": "10aa5b9b4ea072110591f44de91ad83bcadcde92..e18520c2388cc6132fcda418cd6e62396bb5efe3"
}]
diff --git a/test/corpus/diff-summaries/ruby/delimiter.json b/test/corpus/diff-summaries/ruby/delimiter.json
index db20a14e4..92b7b1a2a 100644
--- a/test/corpus/diff-summaries/ruby/delimiter.json
+++ b/test/corpus/diff-summaries/ruby/delimiter.json
@@ -72,7 +72,7 @@
"+%Qc>"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e3bf2ed1e31569b6093ee1fc86e4cc8340ca76d7..f169c2b7eccf7f9fdc895ea8ac1042a82eaa0830"
+ "shas": "5461881a7d85f56771a5a9f4584204bead4a4fe3..7ecd9ad1b3a0d9f7fb86bc605fe02a3cacdd9790"
}
,{
"testCaseDescription": "ruby-delimiter-replacement-insert-test",
@@ -136,7 +136,7 @@
" %#a#"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f169c2b7eccf7f9fdc895ea8ac1042a82eaa0830..c6d854bdd98c01795b876d06a196c34a0554bf8b"
+ "shas": "7ecd9ad1b3a0d9f7fb86bc605fe02a3cacdd9790..22b1b0f6d39c73c3024e5d5e738e1b3da19b1dfa"
}
,{
"testCaseDescription": "ruby-delimiter-delete-insert-test",
@@ -200,7 +200,7 @@
" %#a#"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c6d854bdd98c01795b876d06a196c34a0554bf8b..75e318a517253a5d70efff9d2c9a36cc3574b01f"
+ "shas": "22b1b0f6d39c73c3024e5d5e738e1b3da19b1dfa..c846bedb2d47e51659431c14c6012eae36adc70f"
}
,{
"testCaseDescription": "ruby-delimiter-replacement-test",
@@ -264,7 +264,7 @@
" %#a#"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "75e318a517253a5d70efff9d2c9a36cc3574b01f..2888bde644c8c79c9858efdb2ad7178e7febda02"
+ "shas": "c846bedb2d47e51659431c14c6012eae36adc70f..ed1100ea0cc4e8295fabd092dea3a448c7ebcc00"
}
,{
"testCaseDescription": "ruby-delimiter-delete-replacement-test",
@@ -337,7 +337,7 @@
"+%Q{d{e}f}"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2888bde644c8c79c9858efdb2ad7178e7febda02..fe305a3e338da14342a57d5b931e2c76c76f5088"
+ "shas": "ed1100ea0cc4e8295fabd092dea3a448c7ebcc00..7797487ea3a20444838cb881162baa8da242896c"
}
,{
"testCaseDescription": "ruby-delimiter-delete-test",
@@ -395,7 +395,7 @@
" %/b/"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fe305a3e338da14342a57d5b931e2c76c76f5088..a113a1937711ee8a6d5814a05f23acd802450a90"
+ "shas": "7797487ea3a20444838cb881162baa8da242896c..9970f68e2870be053194fafc21538bf50901a21b"
}
,{
"testCaseDescription": "ruby-delimiter-delete-rest-test",
@@ -438,5 +438,5 @@
"-%Q{d{e}f}"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a113a1937711ee8a6d5814a05f23acd802450a90..0f6cb87a146aa3332ff673d24b8c4756cad55afc"
+ "shas": "9970f68e2870be053194fafc21538bf50901a21b..69c468268d84fab966b5c2051e6139c7bdc7e2e9"
}]
diff --git a/test/corpus/diff-summaries/ruby/element-reference.json b/test/corpus/diff-summaries/ruby/element-reference.json
index 58a4bf3cc..82f4d1a38 100644
--- a/test/corpus/diff-summaries/ruby/element-reference.json
+++ b/test/corpus/diff-summaries/ruby/element-reference.json
@@ -66,7 +66,7 @@
"+foo[bar] = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1aea9068dbdffb0bbd5c543d592d8c0479573e14..25e55f37d4b32b3c64f736bfd2def380021bdf39"
+ "shas": "16867ccacb6652a837e04e836ec69aaba1a2c63e..98199e2ac3bc0b8e7948925df0178edd0b1cfa7e"
}
,{
"testCaseDescription": "ruby-element-reference-replacement-insert-test",
@@ -171,7 +171,7 @@
" foo[bar] = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "25e55f37d4b32b3c64f736bfd2def380021bdf39..a0e8a9e5cf524f12360d9e2eab204d821e508836"
+ "shas": "98199e2ac3bc0b8e7948925df0178edd0b1cfa7e..1661ecbe008dc38140dab0cfbb89f51b705da6b9"
}
,{
"testCaseDescription": "ruby-element-reference-delete-insert-test",
@@ -297,7 +297,7 @@
" foo[bar] = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a0e8a9e5cf524f12360d9e2eab204d821e508836..c9dcc58a813be36814447378d15f5a76cbdf4d85"
+ "shas": "1661ecbe008dc38140dab0cfbb89f51b705da6b9..2bd57953f7cbd2f0f5290dbce5e4e9c82e3f0224"
}
,{
"testCaseDescription": "ruby-element-reference-replacement-test",
@@ -423,7 +423,7 @@
" foo[bar] = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c9dcc58a813be36814447378d15f5a76cbdf4d85..ac3e2c08df0b4dc19d7d0b3d480a8914a4c607fe"
+ "shas": "2bd57953f7cbd2f0f5290dbce5e4e9c82e3f0224..e880a7617608b3719cd03365fc88b6afe1084771"
}
,{
"testCaseDescription": "ruby-element-reference-delete-replacement-test",
@@ -560,7 +560,7 @@
"+x[:\"c\"]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ac3e2c08df0b4dc19d7d0b3d480a8914a4c607fe..2c7978e36b430dbfaa2a5b0da1830509e3aca00d"
+ "shas": "e880a7617608b3719cd03365fc88b6afe1084771..a3809c17a3c04414c121c749fc69895a6d925a64"
}
,{
"testCaseDescription": "ruby-element-reference-delete-test",
@@ -632,7 +632,7 @@
" x[:\"c\"]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2c7978e36b430dbfaa2a5b0da1830509e3aca00d..3398b8b0cf9e88eb2512e2cf75fdea03ad0c7b1b"
+ "shas": "a3809c17a3c04414c121c749fc69895a6d925a64..1d5e999da055542a7266649a037ad21b84f6ab74"
}
,{
"testCaseDescription": "ruby-element-reference-delete-rest-test",
@@ -686,5 +686,5 @@
"-x[:\"c\"]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3398b8b0cf9e88eb2512e2cf75fdea03ad0c7b1b..166c92e7981b72600fa1e5096d0be628cc8d962c"
+ "shas": "1d5e999da055542a7266649a037ad21b84f6ab74..a07975f1b55276cfbfa8bc5865e2ad77f0b12b14"
}]
diff --git a/test/corpus/diff-summaries/ruby/else.json b/test/corpus/diff-summaries/ruby/else.json
index f1a4ed7e4..6218a0191 100644
--- a/test/corpus/diff-summaries/ruby/else.json
+++ b/test/corpus/diff-summaries/ruby/else.json
@@ -36,7 +36,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5127fe99b505deff8beb2b738a1225eaaaee825f..86d63ca274c0865badae15122e38d1e366cfaf94"
+ "shas": "a60c38ac8820bc400cce7a8a87001d1c9b8889ff..ceab7b0639fbb34a6a12d624e06a05046d8e47c1"
}
,{
"testCaseDescription": "ruby-else-insert-test",
@@ -77,7 +77,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "86d63ca274c0865badae15122e38d1e366cfaf94..e521a84a5a7fac228959521bb9c5107e64e1a90a"
+ "shas": "ceab7b0639fbb34a6a12d624e06a05046d8e47c1..dc045f02b0dfb7dca7fe2aabfe444ff3193a4787"
}
,{
"testCaseDescription": "ruby-else-replacement-test",
@@ -131,7 +131,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e521a84a5a7fac228959521bb9c5107e64e1a90a..40369a29a5a69d8e399e26d3c4d0c16ca2522e6e"
+ "shas": "dc045f02b0dfb7dca7fe2aabfe444ff3193a4787..93090f5f67df2e2ff452323bafb6cac43c119664"
}
,{
"testCaseDescription": "ruby-else-delete-replacement-test",
@@ -185,7 +185,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "40369a29a5a69d8e399e26d3c4d0c16ca2522e6e..d53132e4ef60c246d47403d7619c62bbe0eb9216"
+ "shas": "93090f5f67df2e2ff452323bafb6cac43c119664..473c0a98bf7716240bd92b38885f447e2a02f651"
}
,{
"testCaseDescription": "ruby-else-delete-insert-test",
@@ -226,7 +226,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d53132e4ef60c246d47403d7619c62bbe0eb9216..fd5cbc922c0c10436c763fc15e574d90ce1c3bbb"
+ "shas": "473c0a98bf7716240bd92b38885f447e2a02f651..778803f70e907610c1a4d59ffb2ca7ddc7211918"
}
,{
"testCaseDescription": "ruby-else-teardown-test",
@@ -266,5 +266,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fd5cbc922c0c10436c763fc15e574d90ce1c3bbb..c121edce8d75129944087d6c723ebd4b3b34f658"
+ "shas": "778803f70e907610c1a4d59ffb2ca7ddc7211918..344aedc27d9ad2c6c85480611c65dd5f2064182a"
}]
diff --git a/test/corpus/diff-summaries/ruby/elsif.json b/test/corpus/diff-summaries/ruby/elsif.json
index 74b654bf9..9ffd75494 100644
--- a/test/corpus/diff-summaries/ruby/elsif.json
+++ b/test/corpus/diff-summaries/ruby/elsif.json
@@ -36,7 +36,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c121edce8d75129944087d6c723ebd4b3b34f658..a5047ae38624d3b39b10226f45423f58a5421ed8"
+ "shas": "344aedc27d9ad2c6c85480611c65dd5f2064182a..13a4de5cf3b88bd49a772dc3e407cb9197bdc7c7"
}
,{
"testCaseDescription": "ruby-elsif-insert-test",
@@ -77,7 +77,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a5047ae38624d3b39b10226f45423f58a5421ed8..c99e2d50d89f60222355fc2904878dd670dc8570"
+ "shas": "13a4de5cf3b88bd49a772dc3e407cb9197bdc7c7..625d646514ff742c57df563a5a870ac890721f6f"
}
,{
"testCaseDescription": "ruby-elsif-replacement-test",
@@ -119,7 +119,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c99e2d50d89f60222355fc2904878dd670dc8570..e810202d3b43983fdb819bc5f1d0ac066c410385"
+ "shas": "625d646514ff742c57df563a5a870ac890721f6f..18104348f88798bc2a2268ac35436b23b8d7e7b0"
}
,{
"testCaseDescription": "ruby-elsif-delete-replacement-test",
@@ -161,7 +161,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e810202d3b43983fdb819bc5f1d0ac066c410385..81e19a920356775dad5ded10adb1d55f34500ae8"
+ "shas": "18104348f88798bc2a2268ac35436b23b8d7e7b0..c40ca04b72564f16777de075acf977a0167561d9"
}
,{
"testCaseDescription": "ruby-elsif-delete-insert-test",
@@ -202,7 +202,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "81e19a920356775dad5ded10adb1d55f34500ae8..5dc564a05b96ac7545ffac4596a20ec4531aae91"
+ "shas": "c40ca04b72564f16777de075acf977a0167561d9..62847ae0f08b9683adf1eb6d1f4bafa544e14a40"
}
,{
"testCaseDescription": "ruby-elsif-teardown-test",
@@ -242,5 +242,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5dc564a05b96ac7545ffac4596a20ec4531aae91..9e37beebab6d54d13e727fa92c3950fbe8b6bc37"
+ "shas": "62847ae0f08b9683adf1eb6d1f4bafa544e14a40..52a995458e208bd0e1b31154f64e58ebb3048054"
}]
diff --git a/test/corpus/diff-summaries/ruby/end-block.json b/test/corpus/diff-summaries/ruby/end-block.json
index 8cdf8ee3d..5bd68e1b4 100644
--- a/test/corpus/diff-summaries/ruby/end-block.json
+++ b/test/corpus/diff-summaries/ruby/end-block.json
@@ -36,7 +36,7 @@
"+}"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "bc59f083f15dede23c12c1777479b8f0ea372aaa..da317f0a13ac0f1da243e19a7ee7f11e82936b52"
+ "shas": "51638d239b4fc813f309e3143df19945f9134fc9..ef0b65bf1d55bcf491b2eedf99a97ea6b075adea"
}
,{
"testCaseDescription": "ruby-end-block-replacement-insert-test",
@@ -113,7 +113,7 @@
" }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "da317f0a13ac0f1da243e19a7ee7f11e82936b52..3f23e2cd1f98f46bb6fe4e646b37ac7f846f8c42"
+ "shas": "ef0b65bf1d55bcf491b2eedf99a97ea6b075adea..ebcc9b88a189846954cee3468dd48ddaea443c2b"
}
,{
"testCaseDescription": "ruby-end-block-delete-insert-test",
@@ -187,7 +187,7 @@
" foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3f23e2cd1f98f46bb6fe4e646b37ac7f846f8c42..9ad0664022768455ee132d31e2e020e8a1d12d09"
+ "shas": "ebcc9b88a189846954cee3468dd48ddaea443c2b..1b1448b7b64bdaf38ff85c1fd0d4510f06f20c8d"
}
,{
"testCaseDescription": "ruby-end-block-replacement-test",
@@ -258,7 +258,7 @@
" foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9ad0664022768455ee132d31e2e020e8a1d12d09..cd2a631c242a56b1bb1900a99ce4dafb8d5f5aaf"
+ "shas": "1b1448b7b64bdaf38ff85c1fd0d4510f06f20c8d..381b8bd8de4e3ce5ed81f84463f2b5e49f4f13b7"
}
,{
"testCaseDescription": "ruby-end-block-delete-replacement-test",
@@ -307,7 +307,7 @@
" }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cd2a631c242a56b1bb1900a99ce4dafb8d5f5aaf..d137bde979050feb00f03adfaf9111ee73af3d8a"
+ "shas": "381b8bd8de4e3ce5ed81f84463f2b5e49f4f13b7..8753e2b5bd0795b3e9a46c8b91bd13551cb14116"
}
,{
"testCaseDescription": "ruby-end-block-delete-test",
@@ -350,7 +350,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d137bde979050feb00f03adfaf9111ee73af3d8a..0bec960a4dda6674815c3c4c5ac8c9e1891a06b5"
+ "shas": "8753e2b5bd0795b3e9a46c8b91bd13551cb14116..0f165bbc486203eb3eac04c7583feacadbf5011f"
}
,{
"testCaseDescription": "ruby-end-block-delete-rest-test",
@@ -406,5 +406,5 @@
"-}"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0bec960a4dda6674815c3c4c5ac8c9e1891a06b5..97513ccc92beee8dc279d44117dce9155e578efe"
+ "shas": "0f165bbc486203eb3eac04c7583feacadbf5011f..d873b65ce39ee8f41bdbdb381d42fa08d4d6828b"
}]
diff --git a/test/corpus/diff-summaries/ruby/ensure.json b/test/corpus/diff-summaries/ruby/ensure.json
index 2bfe2f698..577cd8a85 100644
--- a/test/corpus/diff-summaries/ruby/ensure.json
+++ b/test/corpus/diff-summaries/ruby/ensure.json
@@ -36,7 +36,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9e37beebab6d54d13e727fa92c3950fbe8b6bc37..42bdf634b36e99a750c4f41553ec57fbe5e9f950"
+ "shas": "52a995458e208bd0e1b31154f64e58ebb3048054..10af3fda97bb5488ebc258b5fa9ff2b088c5c566"
}
,{
"testCaseDescription": "ruby-ensure-insert-test",
@@ -77,7 +77,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "42bdf634b36e99a750c4f41553ec57fbe5e9f950..7f1ed0cc7b67f2a59c652de898fe9b3c0ede003f"
+ "shas": "10af3fda97bb5488ebc258b5fa9ff2b088c5c566..c449b52c2f99e661c948001306bf7c9f9c300122"
}
,{
"testCaseDescription": "ruby-ensure-replacement-test",
@@ -131,7 +131,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7f1ed0cc7b67f2a59c652de898fe9b3c0ede003f..f7c1ecc5dc3c3da4d2aa5ebadcffc1dff1efa97a"
+ "shas": "c449b52c2f99e661c948001306bf7c9f9c300122..e26ad3e9cca0c295d03ba11973a4536da8a13467"
}
,{
"testCaseDescription": "ruby-ensure-delete-replacement-test",
@@ -185,7 +185,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f7c1ecc5dc3c3da4d2aa5ebadcffc1dff1efa97a..89fa50850c22a023072a0b562c61577448f8dc4a"
+ "shas": "e26ad3e9cca0c295d03ba11973a4536da8a13467..41a2b9a32586a982b5d0e3043f97555c5ae4c1ff"
}
,{
"testCaseDescription": "ruby-ensure-delete-insert-test",
@@ -226,7 +226,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "89fa50850c22a023072a0b562c61577448f8dc4a..54159298eb4125b9aacf3ca8db605584694ce8a2"
+ "shas": "41a2b9a32586a982b5d0e3043f97555c5ae4c1ff..2e3bd1f213800651c96b9b6d9dd031840dd5128e"
}
,{
"testCaseDescription": "ruby-ensure-teardown-test",
@@ -266,5 +266,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "54159298eb4125b9aacf3ca8db605584694ce8a2..5cc243cda94fa2788a86c16754a39ec988628dbb"
+ "shas": "2e3bd1f213800651c96b9b6d9dd031840dd5128e..3ed4858d0df31fefc47cf20d5f24390fd8aad9ce"
}]
diff --git a/test/corpus/diff-summaries/ruby/for.json b/test/corpus/diff-summaries/ruby/for.json
index 9b4bd9225..24090748e 100644
--- a/test/corpus/diff-summaries/ruby/for.json
+++ b/test/corpus/diff-summaries/ruby/for.json
@@ -36,7 +36,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b55e70db0fed4efeb4bb9f9b7abd3bba675a1ec3..63e08d362d334e13462d5e04802214a92ae9dc2b"
+ "shas": "9c0ac9c6243961b3f6c64e710fd4bd132ba6f0dc..f89a506947978546282fdfae72888a119bf8dc3e"
}
,{
"testCaseDescription": "ruby-for-replacement-insert-test",
@@ -97,7 +97,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "63e08d362d334e13462d5e04802214a92ae9dc2b..f59f4aaa825284676bcedb2d7adf6cafd7abe651"
+ "shas": "f89a506947978546282fdfae72888a119bf8dc3e..cd9a6e76ae555bb85ebfb2cc227116879bd8aae4"
}
,{
"testCaseDescription": "ruby-for-delete-insert-test",
@@ -153,7 +153,7 @@
" f"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f59f4aaa825284676bcedb2d7adf6cafd7abe651..5af410c3d019faf93cd1afa32259a165fa08d997"
+ "shas": "cd9a6e76ae555bb85ebfb2cc227116879bd8aae4..b29e68979fed249b02784d214347435c79b9440e"
}
,{
"testCaseDescription": "ruby-for-replacement-test",
@@ -209,7 +209,7 @@
" f"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5af410c3d019faf93cd1afa32259a165fa08d997..d7755505944f21d2f7dbea4c7ef53443538ed38c"
+ "shas": "b29e68979fed249b02784d214347435c79b9440e..83412ba9f1aa52c29dc6e682a51a0094f2949f29"
}
,{
"testCaseDescription": "ruby-for-delete-replacement-test",
@@ -287,7 +287,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d7755505944f21d2f7dbea4c7ef53443538ed38c..c220e0c27262ee44b884a761a26b9feed83e5c08"
+ "shas": "83412ba9f1aa52c29dc6e682a51a0094f2949f29..fd5b26f34f8f9fc0d2eaf5784e0cb0f17ae5f2cd"
}
,{
"testCaseDescription": "ruby-for-delete-test",
@@ -330,7 +330,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c220e0c27262ee44b884a761a26b9feed83e5c08..d274c04cda54ce07414cc3bfeb507c4471cc7d33"
+ "shas": "fd5b26f34f8f9fc0d2eaf5784e0cb0f17ae5f2cd..d25dde1929afc434f56ea3e39a9b22596c2840d4"
}
,{
"testCaseDescription": "ruby-for-delete-rest-test",
@@ -370,5 +370,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d274c04cda54ce07414cc3bfeb507c4471cc7d33..1aea9068dbdffb0bbd5c543d592d8c0479573e14"
+ "shas": "d25dde1929afc434f56ea3e39a9b22596c2840d4..16867ccacb6652a837e04e836ec69aaba1a2c63e"
}]
diff --git a/test/corpus/diff-summaries/ruby/hash.json b/test/corpus/diff-summaries/ruby/hash.json
index 676ebd407..003a722cb 100644
--- a/test/corpus/diff-summaries/ruby/hash.json
+++ b/test/corpus/diff-summaries/ruby/hash.json
@@ -34,7 +34,7 @@
"+{ :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "15350025c06bebe12d0443222898e58cfdc9bfad..a5f26c6e327dac25dc97488c408a43c8eaef1d57"
+ "shas": "28aa7f167c9cd13555c78c78ce2484539360f682..fb1de565e2cc778cb231a73924db4a9920addbbb"
}
,{
"testCaseDescription": "ruby-hash-replacement-insert-test",
@@ -89,7 +89,7 @@
" { :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a5f26c6e327dac25dc97488c408a43c8eaef1d57..0a4c3be2576b842bb88b10fe32b28164f173f41e"
+ "shas": "fb1de565e2cc778cb231a73924db4a9920addbbb..98408920d932ab23e26ffb5b2b708256ffb8315a"
}
,{
"testCaseDescription": "ruby-hash-delete-insert-test",
@@ -217,7 +217,7 @@
" { :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0a4c3be2576b842bb88b10fe32b28164f173f41e..c85233ca3e2a48e147e6e9ddaecc83467639bffa"
+ "shas": "98408920d932ab23e26ffb5b2b708256ffb8315a..d811903585a5b32ff4e439adeac6aad06493b819"
}
,{
"testCaseDescription": "ruby-hash-replacement-test",
@@ -342,7 +342,7 @@
" { :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c85233ca3e2a48e147e6e9ddaecc83467639bffa..57a74b0f487be79104e7ed0cec196ea164004b22"
+ "shas": "d811903585a5b32ff4e439adeac6aad06493b819..401c4211b7bc33a4a8faf012dd53dc46537afbda"
}
,{
"testCaseDescription": "ruby-hash-delete-replacement-test",
@@ -413,7 +413,7 @@
"+{ key1: \"changed value\", key2: 2, key3: true }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "57a74b0f487be79104e7ed0cec196ea164004b22..9a6c1e5f0f81c57262ca22331aacc2636eb44454"
+ "shas": "401c4211b7bc33a4a8faf012dd53dc46537afbda..56a51631438c4138df33af83893f40b489e959d4"
}
,{
"testCaseDescription": "ruby-hash-delete-test",
@@ -452,7 +452,7 @@
" { key1: \"changed value\", key2: 2, key3: true }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9a6c1e5f0f81c57262ca22331aacc2636eb44454..621b7625965eff81d4e4a06535bbc9ea182b06bc"
+ "shas": "56a51631438c4138df33af83893f40b489e959d4..7eb0c4a41815eb77d7622b942efd4ba10418eb2b"
}
,{
"testCaseDescription": "ruby-hash-delete-rest-test",
@@ -490,5 +490,5 @@
"-{ key1: \"changed value\", key2: 2, key3: true }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "621b7625965eff81d4e4a06535bbc9ea182b06bc..2412502f463a0cb9416638cc2da07ab2d024a52f"
+ "shas": "7eb0c4a41815eb77d7622b942efd4ba10418eb2b..502a790cb75c5cd2f5a1166305c358bca7535c16"
}]
diff --git a/test/corpus/diff-summaries/ruby/if-unless-modifiers.json b/test/corpus/diff-summaries/ruby/if-unless-modifiers.json
index 1ae952a7f..34000f413 100644
--- a/test/corpus/diff-summaries/ruby/if-unless-modifiers.json
+++ b/test/corpus/diff-summaries/ruby/if-unless-modifiers.json
@@ -34,7 +34,7 @@
"+print unless foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0b7a3e0fb3d3a8a872b3fb94475d217170c8c393..e79eb823bb3c0b9f605908c5534beb41e1f425cb"
+ "shas": "d3c95751ff245559adc954a95a654ee6372e17d9..80cd93375817100b69f6bd0284c24b973807c112"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-replacement-insert-test",
@@ -89,7 +89,7 @@
" print unless foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e79eb823bb3c0b9f605908c5534beb41e1f425cb..4db3cae76277e6d2fd84a279124425964dfecfe6"
+ "shas": "80cd93375817100b69f6bd0284c24b973807c112..c5bc99730ef5946276bc1d6910b5000523d9f4c7"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-insert-test",
@@ -145,7 +145,7 @@
" print unless foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4db3cae76277e6d2fd84a279124425964dfecfe6..fa057bdc78eabc698867b938b89ee9f8009eca57"
+ "shas": "c5bc99730ef5946276bc1d6910b5000523d9f4c7..a4f33b64c802fb62b2e5d7931689e2b897cad06d"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-replacement-test",
@@ -201,7 +201,7 @@
" print unless foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fa057bdc78eabc698867b938b89ee9f8009eca57..051983723d56a38f226a335e8b7350f7c56e35fb"
+ "shas": "a4f33b64c802fb62b2e5d7931689e2b897cad06d..18f3b4947c1ebf9ac9b7a2fd0f2c6069527433b6"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-replacement-test",
@@ -272,7 +272,7 @@
"+print if foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "051983723d56a38f226a335e8b7350f7c56e35fb..4772fa7e1eb7a92255972ade65caf4ecdb8960f7"
+ "shas": "18f3b4947c1ebf9ac9b7a2fd0f2c6069527433b6..f4043144de7c29474ecdf4f321d3121208bc8cce"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-test",
@@ -311,7 +311,7 @@
" print if foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4772fa7e1eb7a92255972ade65caf4ecdb8960f7..6a01aa7535355c52bfc42113a46f9596705ffb97"
+ "shas": "f4043144de7c29474ecdf4f321d3121208bc8cce..39d7968182b2889e6f6d58c4a2d98b1978d6aaf9"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-rest-test",
@@ -349,5 +349,5 @@
"-print if foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6a01aa7535355c52bfc42113a46f9596705ffb97..760d160893f207bd4480bd4cdbf9225479c045c8"
+ "shas": "39d7968182b2889e6f6d58c4a2d98b1978d6aaf9..205ba4865cabb2363522ff4a941ac640364c78b9"
}]
diff --git a/test/corpus/diff-summaries/ruby/if.json b/test/corpus/diff-summaries/ruby/if.json
index c6008a458..4495071b7 100644
--- a/test/corpus/diff-summaries/ruby/if.json
+++ b/test/corpus/diff-summaries/ruby/if.json
@@ -40,7 +40,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d77defc8ba86b790d4e36ddebce231ba3d7ca1ea..cbd48390b5e96870ee04b45f01f84c28d22e88d1"
+ "shas": "29a4ecc1f6a17f51d8dcbdb74ddaefc6e651d7ca..15fd006db296eb8203d7079ab59b1db538215a1c"
}
,{
"testCaseDescription": "ruby-if-replacement-insert-test",
@@ -121,7 +121,7 @@
" elsif quux"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cbd48390b5e96870ee04b45f01f84c28d22e88d1..4e175538cb225474e98955be634042c23339a9c2"
+ "shas": "15fd006db296eb8203d7079ab59b1db538215a1c..3ff42fdf91581275e836a9adde93abce5944610c"
}
,{
"testCaseDescription": "ruby-if-delete-insert-test",
@@ -227,7 +227,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4e175538cb225474e98955be634042c23339a9c2..262e64cb9e014a682a3076055054f53a92dc64e8"
+ "shas": "3ff42fdf91581275e836a9adde93abce5944610c..4fe20093da590aad36f6d8fc2498a545b1bfd02a"
}
,{
"testCaseDescription": "ruby-if-replacement-test",
@@ -333,7 +333,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "262e64cb9e014a682a3076055054f53a92dc64e8..14b8a6d274fd61966abe1a82dae5f3fc318525da"
+ "shas": "4fe20093da590aad36f6d8fc2498a545b1bfd02a..7cb4148990be9da0fd3301abbc745e4e09c47d38"
}
,{
"testCaseDescription": "ruby-if-delete-replacement-test",
@@ -391,7 +391,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "14b8a6d274fd61966abe1a82dae5f3fc318525da..b2a6cd4d30d72363c20768449bf41df3d9c3e2f5"
+ "shas": "7cb4148990be9da0fd3301abbc745e4e09c47d38..c1bc12a86c1565497478489d27875554d115ea47"
}
,{
"testCaseDescription": "ruby-if-delete-test",
@@ -438,7 +438,7 @@
" if y then"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b2a6cd4d30d72363c20768449bf41df3d9c3e2f5..d2b02415f29352dbeb60f2ec9fcf6673b9d5f897"
+ "shas": "c1bc12a86c1565497478489d27875554d115ea47..b0e2ce348b9b8c204a2d53a7260fc7176ccd8ffd"
}
,{
"testCaseDescription": "ruby-if-delete-rest-test",
@@ -494,5 +494,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d2b02415f29352dbeb60f2ec9fcf6673b9d5f897..1ab25fb6630b041158518fa5f0e383c7cabbb087"
+ "shas": "b0e2ce348b9b8c204a2d53a7260fc7176ccd8ffd..3300daf6934aa86cb2ac7a51a11812902873e876"
}]
diff --git a/test/corpus/diff-summaries/ruby/interpolation.json b/test/corpus/diff-summaries/ruby/interpolation.json
index bfbe8c5e7..7e5d771c2 100644
--- a/test/corpus/diff-summaries/ruby/interpolation.json
+++ b/test/corpus/diff-summaries/ruby/interpolation.json
@@ -50,7 +50,7 @@
"+\"foo #{bar}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7d1d1ea962e005a0b1ed1d2dc9a165478d2aa972..bff76bee1706d3b868595139b6d8bac93a945617"
+ "shas": "ef0883c98e45e316c23578fc4159905d0093fd66..8f9f1661cb95508b9eec2c91cd830189f02da841"
}
,{
"testCaseDescription": "ruby-interpolation-replacement-insert-test",
@@ -138,7 +138,7 @@
" \"foo #{bar}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "bff76bee1706d3b868595139b6d8bac93a945617..7ee8a2039500750fc30a20adf2da332ce98fdaf6"
+ "shas": "8f9f1661cb95508b9eec2c91cd830189f02da841..6d2531ed8db8044766d81ce049bd594ba195f7b2"
}
,{
"testCaseDescription": "ruby-interpolation-delete-insert-test",
@@ -221,7 +221,7 @@
" :\"foo #{bar}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7ee8a2039500750fc30a20adf2da332ce98fdaf6..ca71bef8f7998f692a2dd649492d240f05765d9c"
+ "shas": "6d2531ed8db8044766d81ce049bd594ba195f7b2..97b4fb59675914d478dc70563ce153d490de8c6a"
}
,{
"testCaseDescription": "ruby-interpolation-replacement-test",
@@ -304,7 +304,7 @@
" :\"foo #{bar}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ca71bef8f7998f692a2dd649492d240f05765d9c..e27ce317daa77d780a0eddda330d4fa12a0ee907"
+ "shas": "97b4fb59675914d478dc70563ce153d490de8c6a..9f70bcdbf792625ecd4df3d160198bd3df96e45f"
}
,{
"testCaseDescription": "ruby-interpolation-delete-replacement-test",
@@ -424,7 +424,7 @@
"+\"bar #{foo}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e27ce317daa77d780a0eddda330d4fa12a0ee907..c2396f508190956f31e2d361684e61d7c8a353c1"
+ "shas": "9f70bcdbf792625ecd4df3d160198bd3df96e45f..04aa5d6306d2cb3c956b3c6bc1f9d18279c972c8"
}
,{
"testCaseDescription": "ruby-interpolation-delete-test",
@@ -480,7 +480,7 @@
" \"bar #{foo}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c2396f508190956f31e2d361684e61d7c8a353c1..9f721d811c37ecf88048e0a128476731acceda72"
+ "shas": "04aa5d6306d2cb3c956b3c6bc1f9d18279c972c8..ba8b0370f60a72fdad7b48c3f3e92ff915b51ac7"
}
,{
"testCaseDescription": "ruby-interpolation-delete-rest-test",
@@ -534,5 +534,5 @@
"-\"bar #{foo}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9f721d811c37ecf88048e0a128476731acceda72..e3bf2ed1e31569b6093ee1fc86e4cc8340ca76d7"
+ "shas": "ba8b0370f60a72fdad7b48c3f3e92ff915b51ac7..5461881a7d85f56771a5a9f4584204bead4a4fe3"
}]
diff --git a/test/corpus/diff-summaries/ruby/lambda-dash-rocket.json b/test/corpus/diff-summaries/ruby/lambda-dash-rocket.json
index 39d078ed4..2798f7c34 100644
--- a/test/corpus/diff-summaries/ruby/lambda-dash-rocket.json
+++ b/test/corpus/diff-summaries/ruby/lambda-dash-rocket.json
@@ -37,7 +37,7 @@
"+}"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6c8dc9471a192b2a2dbb0003b78e81330f92875e..0e3ad0bc035f4bef32cdae66364ff9e77ff366a9"
+ "shas": "0caec37a9c91cd2e743845adbd4fd52f27f01026..a45b4fae15ea9032e3a965f5756a8e879d2e4724"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-replacement-insert-test",
@@ -97,7 +97,7 @@
" 2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0e3ad0bc035f4bef32cdae66364ff9e77ff366a9..f72c36b166376c06a4c3c1494f2fba5d8e607db9"
+ "shas": "a45b4fae15ea9032e3a965f5756a8e879d2e4724..25e21682a602678a59224731c10962553a48c722"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-insert-test",
@@ -154,7 +154,7 @@
" 2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f72c36b166376c06a4c3c1494f2fba5d8e607db9..3602c854baba05719e2473c2e770b0420fe3bdcb"
+ "shas": "25e21682a602678a59224731c10962553a48c722..9714bbf76420f5cc75ec7bfc72e0b5f1f98f94b5"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-replacement-test",
@@ -211,7 +211,7 @@
" 2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3602c854baba05719e2473c2e770b0420fe3bdcb..47e5dcb1ecb14a79fed814b95d909175b46d1c24"
+ "shas": "9714bbf76420f5cc75ec7bfc72e0b5f1f98f94b5..c690677094a7903edfa5d7e9b7ea691997c5e0ef"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-replacement-test",
@@ -288,7 +288,7 @@
"+-> { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "47e5dcb1ecb14a79fed814b95d909175b46d1c24..bb2c4d2481919ce99321894e0637fb887d11de53"
+ "shas": "c690677094a7903edfa5d7e9b7ea691997c5e0ef..d87073079b1c4918712a357b3dd17e794ca9b4cd"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-test",
@@ -330,7 +330,7 @@
" -> { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "bb2c4d2481919ce99321894e0637fb887d11de53..96809c020f43fc650541dc00e09e36bb97dd37f4"
+ "shas": "d87073079b1c4918712a357b3dd17e794ca9b4cd..94dcdabe8ed4cfed4a1dbb7f6a9478e8d016c2f8"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-rest-test",
@@ -368,5 +368,5 @@
"--> { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "96809c020f43fc650541dc00e09e36bb97dd37f4..80254f6fe46c2efb3b3eb51842964f6772d59995"
+ "shas": "94dcdabe8ed4cfed4a1dbb7f6a9478e8d016c2f8..1efd06c8672aa7a2c8d6f903a96e8da0b27388f0"
}]
diff --git a/test/corpus/diff-summaries/ruby/lambda.json b/test/corpus/diff-summaries/ruby/lambda.json
index 9a5f9c57f..6dd115acf 100644
--- a/test/corpus/diff-summaries/ruby/lambda.json
+++ b/test/corpus/diff-summaries/ruby/lambda.json
@@ -34,7 +34,7 @@
"+lambda { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "80254f6fe46c2efb3b3eb51842964f6772d59995..6dcc6a297321191fc8f1f452427dd34cf78911a4"
+ "shas": "1efd06c8672aa7a2c8d6f903a96e8da0b27388f0..d54273655394cedc42e598711ddb5ae0c5f40270"
}
,{
"testCaseDescription": "ruby-lambda-replacement-insert-test",
@@ -89,7 +89,7 @@
" lambda { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6dcc6a297321191fc8f1f452427dd34cf78911a4..0bbf66aa7dfd94a56466743c957a7de351c65b70"
+ "shas": "d54273655394cedc42e598711ddb5ae0c5f40270..023c48fd9cfc4540e7c76d0e3f1f35148c579da8"
}
,{
"testCaseDescription": "ruby-lambda-delete-insert-test",
@@ -142,7 +142,7 @@
" lambda { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0bbf66aa7dfd94a56466743c957a7de351c65b70..1579cef8baeb2b625857892c03fafab484a4987a"
+ "shas": "023c48fd9cfc4540e7c76d0e3f1f35148c579da8..418433fb3c7b423286f47718da76ec66d6ac3d17"
}
,{
"testCaseDescription": "ruby-lambda-replacement-test",
@@ -195,7 +195,7 @@
" lambda { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1579cef8baeb2b625857892c03fafab484a4987a..8c0a9223d2ac0f79f181eb11a248220584e2cc5e"
+ "shas": "418433fb3c7b423286f47718da76ec66d6ac3d17..121e6a6e2fb9b4ae907111c115c34e6d93943ef5"
}
,{
"testCaseDescription": "ruby-lambda-delete-replacement-test",
@@ -266,7 +266,7 @@
"+lambda { |x| x + 1 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8c0a9223d2ac0f79f181eb11a248220584e2cc5e..9b06591b0137b440b6a2fe162a8b029da857d2d9"
+ "shas": "121e6a6e2fb9b4ae907111c115c34e6d93943ef5..9ee39fc4ad7f01be287e6ddcac83d765a6addc70"
}
,{
"testCaseDescription": "ruby-lambda-delete-test",
@@ -305,7 +305,7 @@
" lambda { |x| x + 1 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9b06591b0137b440b6a2fe162a8b029da857d2d9..701b02a738b26f28aed4f1d0a067d5ab008f503c"
+ "shas": "9ee39fc4ad7f01be287e6ddcac83d765a6addc70..fc11290dff43a981bd526448226f979ba666ec2b"
}
,{
"testCaseDescription": "ruby-lambda-delete-rest-test",
@@ -343,5 +343,5 @@
"-lambda { |x| x + 1 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "701b02a738b26f28aed4f1d0a067d5ab008f503c..b55e70db0fed4efeb4bb9f9b7abd3bba675a1ec3"
+ "shas": "fc11290dff43a981bd526448226f979ba666ec2b..9c0ac9c6243961b3f6c64e710fd4bd132ba6f0dc"
}]
diff --git a/test/corpus/diff-summaries/ruby/math-assignment.json b/test/corpus/diff-summaries/ruby/math-assignment.json
index bf55c49e5..1791d4298 100644
--- a/test/corpus/diff-summaries/ruby/math-assignment.json
+++ b/test/corpus/diff-summaries/ruby/math-assignment.json
@@ -98,7 +98,7 @@
"+x **= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0f6cb87a146aa3332ff673d24b8c4756cad55afc..340fd37437887d2efee3a6316e184452dbe2721f"
+ "shas": "69c468268d84fab966b5c2051e6139c7bdc7e2e9..1de25010724df4e754a8c122197b1366316fb837"
}
,{
"testCaseDescription": "ruby-math-assignment-replacement-insert-test",
@@ -283,7 +283,7 @@
" x *= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "340fd37437887d2efee3a6316e184452dbe2721f..dea0d5a9f9b5eed83159a5d1b2cc06d0ac25cd64"
+ "shas": "1de25010724df4e754a8c122197b1366316fb837..699f60ff76bba3c3050dcb030bc9b170670ac7de"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-insert-test",
@@ -337,7 +337,7 @@
" x /= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "dea0d5a9f9b5eed83159a5d1b2cc06d0ac25cd64..c9bd7f61a13dfb953d41e1b99d2870e2bcd03d49"
+ "shas": "699f60ff76bba3c3050dcb030bc9b170670ac7de..cae99cf927cd270d3354a95f23bbdd507344bbb6"
}
,{
"testCaseDescription": "ruby-math-assignment-replacement-test",
@@ -391,7 +391,7 @@
" x /= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c9bd7f61a13dfb953d41e1b99d2870e2bcd03d49..24732038442e16f94cfdc7a35526e4d7b73cb730"
+ "shas": "cae99cf927cd270d3354a95f23bbdd507344bbb6..928354765137ef9ec48d16669ee6ad3bf9a3bfdc"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-replacement-test",
@@ -533,7 +533,7 @@
" x /= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "24732038442e16f94cfdc7a35526e4d7b73cb730..fea8ab8c661173c7f6847ef55ddc940074e86a1c"
+ "shas": "928354765137ef9ec48d16669ee6ad3bf9a3bfdc..ab8c5b182122761fd544f10734c29b2783c4a442"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-test",
@@ -638,7 +638,7 @@
" x *= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fea8ab8c661173c7f6847ef55ddc940074e86a1c..5f1518a1190ff29e7afb78e85dfa40cc4801f812"
+ "shas": "ab8c5b182122761fd544f10734c29b2783c4a442..fe1bc476e46dbf6f12ebef96f1cfb39c127a5b2a"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-rest-test",
@@ -740,5 +740,5 @@
"-x **= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5f1518a1190ff29e7afb78e85dfa40cc4801f812..7c923dd9edc785cfae17ddf168ca4f063c7e7604"
+ "shas": "fe1bc476e46dbf6f12ebef96f1cfb39c127a5b2a..050c435fbd32f39fd591765021defb50b60b0d2a"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-calls-hash-args.json b/test/corpus/diff-summaries/ruby/method-calls-hash-args.json
index 7cc9341d9..7984e743e 100644
--- a/test/corpus/diff-summaries/ruby/method-calls-hash-args.json
+++ b/test/corpus/diff-summaries/ruby/method-calls-hash-args.json
@@ -34,7 +34,7 @@
"+foo(:bar => true)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0e49e13e3453f7edca8a126ec0c14f461ff68d2f..380d4a59a54fa8dd55fbf3e9840d9e6ce1b0c0f1"
+ "shas": "5714d35153a9f1e9cda1d243720fca3f96bf3cd6..5285e420d2376a4754efee4710d6e7c3a3cd48e1"
}
,{
"testCaseDescription": "ruby-method-calls-hash-args-replacement-insert-test",
@@ -89,7 +89,7 @@
" foo(:bar => true)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "380d4a59a54fa8dd55fbf3e9840d9e6ce1b0c0f1..975b6926a60c4aec718e994742f23b85eaa1f845"
+ "shas": "5285e420d2376a4754efee4710d6e7c3a3cd48e1..37a3908bd91a94265215d15f356b9a9cbaf30fc0"
}
,{
"testCaseDescription": "ruby-method-calls-hash-args-delete-insert-test",
@@ -130,7 +130,7 @@
" foo(:bar => true)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "975b6926a60c4aec718e994742f23b85eaa1f845..a8a0eec687e5f732303004a27997de5a7e72953e"
+ "shas": "37a3908bd91a94265215d15f356b9a9cbaf30fc0..e063d2f171ba951917bf25f237c71c863489a682"
}
,{
"testCaseDescription": "ruby-method-calls-hash-args-replacement-test",
@@ -171,7 +171,7 @@
" foo(:bar => true)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a8a0eec687e5f732303004a27997de5a7e72953e..278ce6982d8b846d5317d0fcda7d9fd5b277a96a"
+ "shas": "e063d2f171ba951917bf25f237c71c863489a682..28aca89b91848d03ca8e5df57b9095c5af275275"
}
,{
"testCaseDescription": "ruby-method-calls-hash-args-delete-replacement-test",
@@ -242,7 +242,7 @@
"+foo(:bar => true, :baz => 1)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "278ce6982d8b846d5317d0fcda7d9fd5b277a96a..64d73d2a93d05a444d53b04ff8b6b4359ffa4726"
+ "shas": "28aca89b91848d03ca8e5df57b9095c5af275275..ea2247b60b416e12b8a5b13d21fb5131a3f9eee1"
}
,{
"testCaseDescription": "ruby-method-calls-hash-args-delete-test",
@@ -281,7 +281,7 @@
" foo(:bar => true, :baz => 1)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "64d73d2a93d05a444d53b04ff8b6b4359ffa4726..7a84a66e13fa9c093a32421d1c592b7f4a77cf95"
+ "shas": "ea2247b60b416e12b8a5b13d21fb5131a3f9eee1..4a597a4554d6d32e1b193688d249ef2840b1e03b"
}
,{
"testCaseDescription": "ruby-method-calls-hash-args-delete-rest-test",
@@ -319,5 +319,5 @@
"-foo(:bar => true, :baz => 1)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7a84a66e13fa9c093a32421d1c592b7f4a77cf95..ebc16e531db91e278be158e0331d53d4662ad941"
+ "shas": "4a597a4554d6d32e1b193688d249ef2840b1e03b..ef10a31e176341061b8156a6bf867297521bb536"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-calls-keyword-args.json b/test/corpus/diff-summaries/ruby/method-calls-keyword-args.json
index 3ed2ca214..2f19c652f 100644
--- a/test/corpus/diff-summaries/ruby/method-calls-keyword-args.json
+++ b/test/corpus/diff-summaries/ruby/method-calls-keyword-args.json
@@ -34,7 +34,7 @@
"+foo(bar: true)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8fd9b6bcf4028fca906c02d8e834004fbfdbd046..1e47e299825cff5b9e147ee2b034b503e3a23132"
+ "shas": "846050d80352e68008226a9a3a64e51ffc0556a6..b8181286f56dd5403582df496c4b9701a12916e4"
}
,{
"testCaseDescription": "ruby-method-calls-keyword-args-replacement-insert-test",
@@ -89,7 +89,7 @@
" foo(bar: true)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1e47e299825cff5b9e147ee2b034b503e3a23132..d618a3fe3a065468bbe786f8ca02212c0b95cd25"
+ "shas": "b8181286f56dd5403582df496c4b9701a12916e4..be284a57a20624d8d22de614ff435cee60c4f110"
}
,{
"testCaseDescription": "ruby-method-calls-keyword-args-delete-insert-test",
@@ -130,7 +130,7 @@
" foo(bar: true)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d618a3fe3a065468bbe786f8ca02212c0b95cd25..44bf2ae7602cc00c0cb39d837ddd15922ec01dea"
+ "shas": "be284a57a20624d8d22de614ff435cee60c4f110..430831fa2053cce453c71e5cc30769b3448f2811"
}
,{
"testCaseDescription": "ruby-method-calls-keyword-args-replacement-test",
@@ -171,7 +171,7 @@
" foo(bar: true)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "44bf2ae7602cc00c0cb39d837ddd15922ec01dea..973e0c42fd3e5abe68ff79fe3164adff56d25ed2"
+ "shas": "430831fa2053cce453c71e5cc30769b3448f2811..a1ae8ed2e5fed5ec8dcd71762925b43415478689"
}
,{
"testCaseDescription": "ruby-method-calls-keyword-args-delete-replacement-test",
@@ -242,7 +242,7 @@
"+foo(bar: true, baz: 1)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "973e0c42fd3e5abe68ff79fe3164adff56d25ed2..96918e895e720422df10f0c0e00aeae9b6cde5f3"
+ "shas": "a1ae8ed2e5fed5ec8dcd71762925b43415478689..2384bee31763519191157963f97e2896831af67e"
}
,{
"testCaseDescription": "ruby-method-calls-keyword-args-delete-test",
@@ -281,7 +281,7 @@
" foo(bar: true, baz: 1)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "96918e895e720422df10f0c0e00aeae9b6cde5f3..a50ac4461308145e10c775f4a81dc8bf63055084"
+ "shas": "2384bee31763519191157963f97e2896831af67e..63ee06658d693c257ed31c515d73a1039dd9ddda"
}
,{
"testCaseDescription": "ruby-method-calls-keyword-args-delete-rest-test",
@@ -319,5 +319,5 @@
"-foo(bar: true, baz: 1)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a50ac4461308145e10c775f4a81dc8bf63055084..0e49e13e3453f7edca8a126ec0c14f461ff68d2f"
+ "shas": "63ee06658d693c257ed31c515d73a1039dd9ddda..5714d35153a9f1e9cda1d243720fca3f96bf3cd6"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-calls.json b/test/corpus/diff-summaries/ruby/method-calls.json
index 482ba3eb7..6c2bd46c3 100644
--- a/test/corpus/diff-summaries/ruby/method-calls.json
+++ b/test/corpus/diff-summaries/ruby/method-calls.json
@@ -34,7 +34,7 @@
"+x.foo()"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "299869efc374b8413a3edf91e6ebc2e849fc7407..20531c76e9ef8d1cb0295548df44086f526e887b"
+ "shas": "72a3cad651db806512f0e3b0037860629ab63593..711345a67b50d78e3f6dd5ffb40c0ff9fbb43cb2"
}
,{
"testCaseDescription": "ruby-method-calls-replacement-insert-test",
@@ -89,7 +89,7 @@
" x.foo()"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "20531c76e9ef8d1cb0295548df44086f526e887b..75953aeb6a83571263e30b5a466488010df4ef65"
+ "shas": "711345a67b50d78e3f6dd5ffb40c0ff9fbb43cb2..80602b3b0bc5b5cc10ef691c3f33463d1f9a1cb5"
}
,{
"testCaseDescription": "ruby-method-calls-delete-insert-test",
@@ -142,7 +142,7 @@
" x.foo()"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "75953aeb6a83571263e30b5a466488010df4ef65..2c338816ca38184ebeed065cd0b3483f9ef3f25f"
+ "shas": "80602b3b0bc5b5cc10ef691c3f33463d1f9a1cb5..943314067b0326678cf3cf5b08a0f56d033b5dbd"
}
,{
"testCaseDescription": "ruby-method-calls-replacement-test",
@@ -195,7 +195,7 @@
" x.foo()"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2c338816ca38184ebeed065cd0b3483f9ef3f25f..1ed061ce3173113b0970f8069cef959c36ab4fdc"
+ "shas": "943314067b0326678cf3cf5b08a0f56d033b5dbd..aeaac0d2e3bf09d5c200e60fca633292565a7dfa"
}
,{
"testCaseDescription": "ruby-method-calls-delete-replacement-test",
@@ -266,7 +266,7 @@
"+bar()"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1ed061ce3173113b0970f8069cef959c36ab4fdc..2c951b1de15738a98708277ba0638ec85aecd8e9"
+ "shas": "aeaac0d2e3bf09d5c200e60fca633292565a7dfa..775e41c30eb57046a0256f2439d97002d0ac7192"
}
,{
"testCaseDescription": "ruby-method-calls-delete-test",
@@ -305,7 +305,7 @@
" bar()"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2c951b1de15738a98708277ba0638ec85aecd8e9..321b88fa171035a88721e26445ce03e7c9cc552b"
+ "shas": "775e41c30eb57046a0256f2439d97002d0ac7192..229d6057a7c7592f7a049c8db70a478c58284ba0"
}
,{
"testCaseDescription": "ruby-method-calls-delete-rest-test",
@@ -343,5 +343,5 @@
"-bar()"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "321b88fa171035a88721e26445ce03e7c9cc552b..8fd9b6bcf4028fca906c02d8e834004fbfdbd046"
+ "shas": "229d6057a7c7592f7a049c8db70a478c58284ba0..846050d80352e68008226a9a3a64e51ffc0556a6"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-declaration-keyword-param.json b/test/corpus/diff-summaries/ruby/method-declaration-keyword-param.json
index bd3541b28..da22165fb 100644
--- a/test/corpus/diff-summaries/ruby/method-declaration-keyword-param.json
+++ b/test/corpus/diff-summaries/ruby/method-declaration-keyword-param.json
@@ -35,7 +35,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b3edb3f4a99e8c2e595bfd6ddb195a01fdd8f573..b1b0f7fab421afde00aa6d1b5efe1dc3fc02b3bd"
+ "shas": "9feb37874cac5581ef001c084f185f8b5ff224ed..25509b91144583be14f0688fb65bde7087e55253"
}
,{
"testCaseDescription": "ruby-method-declaration-keyword-param-replacement-insert-test",
@@ -93,7 +93,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b1b0f7fab421afde00aa6d1b5efe1dc3fc02b3bd..8bb0b1c60471de84e7037bd5cff85b2979944b89"
+ "shas": "25509b91144583be14f0688fb65bde7087e55253..fab196f5f36faf5433163a336db3e0f68f4e0589"
}
,{
"testCaseDescription": "ruby-method-declaration-keyword-param-delete-insert-test",
@@ -135,7 +135,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8bb0b1c60471de84e7037bd5cff85b2979944b89..88507aa1ef8540bf6b630a0c48291bf871e12fc4"
+ "shas": "fab196f5f36faf5433163a336db3e0f68f4e0589..924433f84a96fdfdafaee50008ad603180a7a393"
}
,{
"testCaseDescription": "ruby-method-declaration-keyword-param-replacement-test",
@@ -177,7 +177,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "88507aa1ef8540bf6b630a0c48291bf871e12fc4..99b4d01a982126ad21a3eae88f23a8d2cfc7fe71"
+ "shas": "924433f84a96fdfdafaee50008ad603180a7a393..a80ef58535435e6234bb4bf087ea77ece0a7aa0d"
}
,{
"testCaseDescription": "ruby-method-declaration-keyword-param-delete-replacement-test",
@@ -251,7 +251,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "99b4d01a982126ad21a3eae88f23a8d2cfc7fe71..96f76e626627010848d601f753e46994b408db90"
+ "shas": "a80ef58535435e6234bb4bf087ea77ece0a7aa0d..793fd59329ac2ac725fc7016b1ae7b8e679edd71"
}
,{
"testCaseDescription": "ruby-method-declaration-keyword-param-delete-test",
@@ -292,7 +292,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "96f76e626627010848d601f753e46994b408db90..e01819fe6134eee044e699c4795d69985254fd44"
+ "shas": "793fd59329ac2ac725fc7016b1ae7b8e679edd71..e6afba0e86ee52e2a8b70983ffc6ebe9d7709803"
}
,{
"testCaseDescription": "ruby-method-declaration-keyword-param-delete-rest-test",
@@ -331,5 +331,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e01819fe6134eee044e699c4795d69985254fd44..94e12ff958b9acab76bca28dda5ddc409b164acd"
+ "shas": "e6afba0e86ee52e2a8b70983ffc6ebe9d7709803..94dd3c25ff063ecc56461aeb30d5609ec2059dec"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-declaration-param-default.json b/test/corpus/diff-summaries/ruby/method-declaration-param-default.json
index 20886506e..824026859 100644
--- a/test/corpus/diff-summaries/ruby/method-declaration-param-default.json
+++ b/test/corpus/diff-summaries/ruby/method-declaration-param-default.json
@@ -35,7 +35,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "94e12ff958b9acab76bca28dda5ddc409b164acd..ba97939163ba5be7d2eb42968d3a7b1da61fa807"
+ "shas": "94dd3c25ff063ecc56461aeb30d5609ec2059dec..adee1a380754febf22b8d8634ede362728202418"
}
,{
"testCaseDescription": "ruby-method-declaration-param-default-replacement-insert-test",
@@ -93,7 +93,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ba97939163ba5be7d2eb42968d3a7b1da61fa807..46c7958d9fa78d9dbbf8b170744a5952f8725213"
+ "shas": "adee1a380754febf22b8d8634ede362728202418..62465e98f3bb980477c24f4d43ca4cecca034c1c"
}
,{
"testCaseDescription": "ruby-method-declaration-param-default-delete-insert-test",
@@ -135,7 +135,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "46c7958d9fa78d9dbbf8b170744a5952f8725213..43b130865f05441230a5838f91e3eddb8a0c2106"
+ "shas": "62465e98f3bb980477c24f4d43ca4cecca034c1c..0bc2fb6de8ff1565864de43f663fc46446f8d6b0"
}
,{
"testCaseDescription": "ruby-method-declaration-param-default-replacement-test",
@@ -177,7 +177,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "43b130865f05441230a5838f91e3eddb8a0c2106..778abb4e3706bc38a64be199c511fbc73b437495"
+ "shas": "0bc2fb6de8ff1565864de43f663fc46446f8d6b0..e746b514c71666c2f6a6285a65cd26c32c9c9309"
}
,{
"testCaseDescription": "ruby-method-declaration-param-default-delete-replacement-test",
@@ -251,7 +251,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "778abb4e3706bc38a64be199c511fbc73b437495..f5a55f21924d4fd3d0a63199eb49bd62b46de97e"
+ "shas": "e746b514c71666c2f6a6285a65cd26c32c9c9309..409c4d1e90472241d2530ff1c8c7b9ba315a005a"
}
,{
"testCaseDescription": "ruby-method-declaration-param-default-delete-test",
@@ -292,7 +292,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f5a55f21924d4fd3d0a63199eb49bd62b46de97e..c32d5d100b0d3904ab67d6043046d9a7499c6542"
+ "shas": "409c4d1e90472241d2530ff1c8c7b9ba315a005a..9f91222ea8643862c97c46800c7206dafe0274d9"
}
,{
"testCaseDescription": "ruby-method-declaration-param-default-delete-rest-test",
@@ -331,5 +331,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c32d5d100b0d3904ab67d6043046d9a7499c6542..3decd374dbdad637d9d37d838e6885ed93890718"
+ "shas": "9f91222ea8643862c97c46800c7206dafe0274d9..751d9599232895a09f4026956452f1dfc86e0c9d"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-declaration-params.json b/test/corpus/diff-summaries/ruby/method-declaration-params.json
index 12ea84662..0c1f1ebd9 100644
--- a/test/corpus/diff-summaries/ruby/method-declaration-params.json
+++ b/test/corpus/diff-summaries/ruby/method-declaration-params.json
@@ -35,7 +35,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f1b6bbddd7c59150a9f8c15746168a84eb3d12cd..9c67c3d54b1988f9dc9d36d133263fb55392f5a5"
+ "shas": "01b13564c812c309867f8f8201bbbebe8f878f4d..b7dd051c8d7021a24eef603c87d14027d19ba043"
}
,{
"testCaseDescription": "ruby-method-declaration-params-insert-test",
@@ -75,7 +75,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9c67c3d54b1988f9dc9d36d133263fb55392f5a5..fa52999f22ea2db5ec6279edc1ce6923b03fa112"
+ "shas": "b7dd051c8d7021a24eef603c87d14027d19ba043..75a68dbeeb7a428a3f86b783db24c1cf5e3c4fc1"
}
,{
"testCaseDescription": "ruby-method-declaration-params-replacement-test",
@@ -130,7 +130,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fa52999f22ea2db5ec6279edc1ce6923b03fa112..0066f7111989f8c16984b561886143c96ccfc653"
+ "shas": "75a68dbeeb7a428a3f86b783db24c1cf5e3c4fc1..77bd11b3d718b733c4aa6b58fe27bd5ca8074e49"
}
,{
"testCaseDescription": "ruby-method-declaration-params-delete-replacement-test",
@@ -185,7 +185,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0066f7111989f8c16984b561886143c96ccfc653..f6bbfebf7315403e68eeeb74b59c36c02d96aca7"
+ "shas": "77bd11b3d718b733c4aa6b58fe27bd5ca8074e49..ecf42398fcfb1b45807c155dcf231429ce55d335"
}
,{
"testCaseDescription": "ruby-method-declaration-params-delete-insert-test",
@@ -225,7 +225,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f6bbfebf7315403e68eeeb74b59c36c02d96aca7..b3f6954afea9828fb56e8dc8bd2f11fc3385f827"
+ "shas": "ecf42398fcfb1b45807c155dcf231429ce55d335..6289c01f7f9b0dead7f8b63f9e86498811e843a1"
}
,{
"testCaseDescription": "ruby-method-declaration-params-teardown-test",
@@ -264,5 +264,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b3f6954afea9828fb56e8dc8bd2f11fc3385f827..90b769d2ee1bd1b62ce2da0ff8b1574c43cca4ec"
+ "shas": "6289c01f7f9b0dead7f8b63f9e86498811e843a1..5458878541d4dbd326730893f8986cee3285d576"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-declaration-required-keyword-param.json b/test/corpus/diff-summaries/ruby/method-declaration-required-keyword-param.json
index fb4f828c3..4e2c614b3 100644
--- a/test/corpus/diff-summaries/ruby/method-declaration-required-keyword-param.json
+++ b/test/corpus/diff-summaries/ruby/method-declaration-required-keyword-param.json
@@ -35,7 +35,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "90b769d2ee1bd1b62ce2da0ff8b1574c43cca4ec..5bf09277984af525ceb322a441be308ed6907cc6"
+ "shas": "5458878541d4dbd326730893f8986cee3285d576..b73bf47832991c4a3399b47b1d27c657d861e609"
}
,{
"testCaseDescription": "ruby-method-declaration-required-keyword-param-replacement-insert-test",
@@ -93,7 +93,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5bf09277984af525ceb322a441be308ed6907cc6..a10e2d7f5ed5beda0cf27077c35a7789609bb487"
+ "shas": "b73bf47832991c4a3399b47b1d27c657d861e609..60fa8a2728763fdb9d2ffa8aa56bbfd2f6967f0b"
}
,{
"testCaseDescription": "ruby-method-declaration-required-keyword-param-delete-insert-test",
@@ -135,7 +135,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a10e2d7f5ed5beda0cf27077c35a7789609bb487..453adff4f51474f3588fa4429a6a1245e70a873e"
+ "shas": "60fa8a2728763fdb9d2ffa8aa56bbfd2f6967f0b..9646f88e1303a125db3c184abcc3a915db7779e5"
}
,{
"testCaseDescription": "ruby-method-declaration-required-keyword-param-replacement-test",
@@ -177,7 +177,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "453adff4f51474f3588fa4429a6a1245e70a873e..88c9b9567055338ff7b82f2a49ab2c2f9804a099"
+ "shas": "9646f88e1303a125db3c184abcc3a915db7779e5..9ce0060c2587e67bfc9ff2e9716b9cb56e1eb09c"
}
,{
"testCaseDescription": "ruby-method-declaration-required-keyword-param-delete-replacement-test",
@@ -251,7 +251,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "88c9b9567055338ff7b82f2a49ab2c2f9804a099..5648133048e1658738d3092f43fc7668482f5784"
+ "shas": "9ce0060c2587e67bfc9ff2e9716b9cb56e1eb09c..c5baaef18232cc643c8c8826e574d4c7842b2fd2"
}
,{
"testCaseDescription": "ruby-method-declaration-required-keyword-param-delete-test",
@@ -292,7 +292,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5648133048e1658738d3092f43fc7668482f5784..cd15336f3cba53668ec8b8b0592bb0a1e42f6d2f"
+ "shas": "c5baaef18232cc643c8c8826e574d4c7842b2fd2..adbc1e83473b1f4efe5207aa66caaf2ee9549c5d"
}
,{
"testCaseDescription": "ruby-method-declaration-required-keyword-param-delete-rest-test",
@@ -331,5 +331,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cd15336f3cba53668ec8b8b0592bb0a1e42f6d2f..b3edb3f4a99e8c2e595bfd6ddb195a01fdd8f573"
+ "shas": "adbc1e83473b1f4efe5207aa66caaf2ee9549c5d..9feb37874cac5581ef001c084f185f8b5ff224ed"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-declaration-unnamed-param.json b/test/corpus/diff-summaries/ruby/method-declaration-unnamed-param.json
index c2a268341..c63116d19 100644
--- a/test/corpus/diff-summaries/ruby/method-declaration-unnamed-param.json
+++ b/test/corpus/diff-summaries/ruby/method-declaration-unnamed-param.json
@@ -35,7 +35,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3decd374dbdad637d9d37d838e6885ed93890718..5c68ea9981cd54b6bcece20d934884c26007cc21"
+ "shas": "751d9599232895a09f4026956452f1dfc86e0c9d..0165030f9f6a2bed54c1d3c8c7a7946199eb30f6"
}
,{
"testCaseDescription": "ruby-method-declaration-unnamed-param-replacement-insert-test",
@@ -93,7 +93,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5c68ea9981cd54b6bcece20d934884c26007cc21..aaf043ef4ad645337ab4742a50b971265c58a774"
+ "shas": "0165030f9f6a2bed54c1d3c8c7a7946199eb30f6..aeb3cca6b0861c378a7b1959be29591354277d95"
}
,{
"testCaseDescription": "ruby-method-declaration-unnamed-param-delete-insert-test",
@@ -135,7 +135,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "aaf043ef4ad645337ab4742a50b971265c58a774..c249bca4ec6d809c7aa48923f26766c762a5e8a4"
+ "shas": "aeb3cca6b0861c378a7b1959be29591354277d95..414db1d7ef19f59548c653e2e82b83756c487d7c"
}
,{
"testCaseDescription": "ruby-method-declaration-unnamed-param-replacement-test",
@@ -177,7 +177,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c249bca4ec6d809c7aa48923f26766c762a5e8a4..a4e66e8601688d52f1a704c09f9b4b26cbb14218"
+ "shas": "414db1d7ef19f59548c653e2e82b83756c487d7c..72e1b85a6e3bafbe4b57a8cfac79c1f384403490"
}
,{
"testCaseDescription": "ruby-method-declaration-unnamed-param-delete-replacement-test",
@@ -251,7 +251,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a4e66e8601688d52f1a704c09f9b4b26cbb14218..50c5d30a9e6b3a2e485d57ccaf01021b7c7b1400"
+ "shas": "72e1b85a6e3bafbe4b57a8cfac79c1f384403490..3c0797fb79d00a47f90d78624b45582ccb774aa8"
}
,{
"testCaseDescription": "ruby-method-declaration-unnamed-param-delete-test",
@@ -292,7 +292,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "50c5d30a9e6b3a2e485d57ccaf01021b7c7b1400..27f0b8f0a320f72e55629cb4a9349e9299631d51"
+ "shas": "3c0797fb79d00a47f90d78624b45582ccb774aa8..aa86d930132b8765e99543541a76d7e45132a44a"
}
,{
"testCaseDescription": "ruby-method-declaration-unnamed-param-delete-rest-test",
@@ -331,5 +331,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "27f0b8f0a320f72e55629cb4a9349e9299631d51..dfda8f91aefa4a3a4bd5db0cfa9c7cae31acfdd0"
+ "shas": "aa86d930132b8765e99543541a76d7e45132a44a..05c70ba2c541eae931b39c6b0f68b26314c70978"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-declaration.json b/test/corpus/diff-summaries/ruby/method-declaration.json
index ff03cf84e..4d9982078 100644
--- a/test/corpus/diff-summaries/ruby/method-declaration.json
+++ b/test/corpus/diff-summaries/ruby/method-declaration.json
@@ -35,7 +35,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "745ee2cc606e7da317050022e6da3954b4cfbddd..272ec6fc6d18341beb6e38eb26173fe13ae81f9f"
+ "shas": "c9bdd0c09a302590952bf0f4b5303baa39e99888..4fd87db0c8bd56a18e86d1143646507f1e8fabfd"
}
,{
"testCaseDescription": "ruby-method-declaration-replacement-insert-test",
@@ -94,7 +94,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "272ec6fc6d18341beb6e38eb26173fe13ae81f9f..d6a6c9cf452f795cbb8ea3645cf5cbac8d2e7be1"
+ "shas": "4fd87db0c8bd56a18e86d1143646507f1e8fabfd..ab45c8b1d757f18b8fc062be82df978d5d66ca00"
}
,{
"testCaseDescription": "ruby-method-declaration-delete-insert-test",
@@ -179,7 +179,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d6a6c9cf452f795cbb8ea3645cf5cbac8d2e7be1..85713c694207db6c2cbfb01f159ddcaaeaa1984f"
+ "shas": "ab45c8b1d757f18b8fc062be82df978d5d66ca00..8fbf07cb22312649ed0b1b2702955b75dcef63d2"
}
,{
"testCaseDescription": "ruby-method-declaration-replacement-test",
@@ -264,7 +264,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "85713c694207db6c2cbfb01f159ddcaaeaa1984f..6d4e2e350c8968ecfbd9319ccc9d4f2a9fd36c0f"
+ "shas": "8fbf07cb22312649ed0b1b2702955b75dcef63d2..4bcaffcdcf8e214e1f7c8f04820dd43d956a4d12"
}
,{
"testCaseDescription": "ruby-method-declaration-delete-replacement-test",
@@ -340,7 +340,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6d4e2e350c8968ecfbd9319ccc9d4f2a9fd36c0f..cdceeff094a352b7e63604cf0185fbb9bfa7cb28"
+ "shas": "4bcaffcdcf8e214e1f7c8f04820dd43d956a4d12..f6fb96c071c72dd540e080112896f6bf14af0389"
}
,{
"testCaseDescription": "ruby-method-declaration-delete-test",
@@ -382,7 +382,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cdceeff094a352b7e63604cf0185fbb9bfa7cb28..f95910c5938c2489dd95129860b9b2dfc320a93c"
+ "shas": "f6fb96c071c72dd540e080112896f6bf14af0389..13130d64d426b314ded5aff883246f742c66929b"
}
,{
"testCaseDescription": "ruby-method-declaration-delete-rest-test",
@@ -422,5 +422,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f95910c5938c2489dd95129860b9b2dfc320a93c..f1b6bbddd7c59150a9f8c15746168a84eb3d12cd"
+ "shas": "13130d64d426b314ded5aff883246f742c66929b..01b13564c812c309867f8f8201bbbebe8f878f4d"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-invocation.json b/test/corpus/diff-summaries/ruby/method-invocation.json
index 9ce4c5100..a7a9b6744 100644
--- a/test/corpus/diff-summaries/ruby/method-invocation.json
+++ b/test/corpus/diff-summaries/ruby/method-invocation.json
@@ -66,7 +66,7 @@
"+bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "dfda8f91aefa4a3a4bd5db0cfa9c7cae31acfdd0..2e1172fee9b8d68ff4c44801d5eb0d706b2de53d"
+ "shas": "05c70ba2c541eae931b39c6b0f68b26314c70978..7a127e8f786be51cbd4262a8d4c1316d5cb132ef"
}
,{
"testCaseDescription": "ruby-method-invocation-replacement-insert-test",
@@ -203,7 +203,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2e1172fee9b8d68ff4c44801d5eb0d706b2de53d..22faacc64a03187f90b0621f5d95c07bc8736dce"
+ "shas": "7a127e8f786be51cbd4262a8d4c1316d5cb132ef..4ff86e482e01384b7718883d28bd4cdd1c4066ee"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-insert-test",
@@ -340,7 +340,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "22faacc64a03187f90b0621f5d95c07bc8736dce..94fc49bab107840bacddd9b33e2c206d5a7e683b"
+ "shas": "4ff86e482e01384b7718883d28bd4cdd1c4066ee..d7e820b2bb0928b10350821c9c4e512e1e47f686"
}
,{
"testCaseDescription": "ruby-method-invocation-replacement-test",
@@ -477,7 +477,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "94fc49bab107840bacddd9b33e2c206d5a7e683b..2c57cda3f33f22ee906d352b4ffde69b7642191e"
+ "shas": "d7e820b2bb0928b10350821c9c4e512e1e47f686..a6ee19055279f074fcdff269868f9f157e882be7"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-replacement-test",
@@ -557,7 +557,7 @@
"-bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2c57cda3f33f22ee906d352b4ffde69b7642191e..f5098efbaf20472a2cd843500a694731f965e36a"
+ "shas": "a6ee19055279f074fcdff269868f9f157e882be7..7c15a46cf8da797bc5a0414c63f4e007a3e22c0b"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-test",
@@ -630,7 +630,7 @@
" bar 2, 3"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f5098efbaf20472a2cd843500a694731f965e36a..bc87e2b95ee3a98bdc7ed89e7ebda5c436fcb157"
+ "shas": "7c15a46cf8da797bc5a0414c63f4e007a3e22c0b..580bf1d3419ec14cbeabd74161c52c1275557dda"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-rest-test",
@@ -716,5 +716,5 @@
"-bar(2, 3)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "bc87e2b95ee3a98bdc7ed89e7ebda5c436fcb157..299869efc374b8413a3edf91e6ebc2e849fc7407"
+ "shas": "580bf1d3419ec14cbeabd74161c52c1275557dda..72a3cad651db806512f0e3b0037860629ab63593"
}]
diff --git a/test/corpus/diff-summaries/ruby/module.json b/test/corpus/diff-summaries/ruby/module.json
index 6adb1b4ef..3122c9031 100644
--- a/test/corpus/diff-summaries/ruby/module.json
+++ b/test/corpus/diff-summaries/ruby/module.json
@@ -35,7 +35,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ab126516af689f66354c40e2b73bad9ea5b34fc4..ac79ecd161c915458417d12e47e707d95fd16738"
+ "shas": "0e65da6c947e134d3e5cd0b5f20b813dd2fc367b..f1bdb8f5062b15c23da5338b1c77a65c75c92170"
}
,{
"testCaseDescription": "ruby-module-replacement-insert-test",
@@ -95,7 +95,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ac79ecd161c915458417d12e47e707d95fd16738..d71fc73ff4f7a02be728477e235d1c084063fd3e"
+ "shas": "f1bdb8f5062b15c23da5338b1c77a65c75c92170..8360737e786bcc1311e5965897d2a4575f77c334"
}
,{
"testCaseDescription": "ruby-module-delete-insert-test",
@@ -138,7 +138,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d71fc73ff4f7a02be728477e235d1c084063fd3e..e20736f3fea1fa2ce7a01c692ee1ea62cbdc8770"
+ "shas": "8360737e786bcc1311e5965897d2a4575f77c334..3c6ea542b73d4634a8ef1f3a4feab21638b44e59"
}
,{
"testCaseDescription": "ruby-module-replacement-test",
@@ -181,7 +181,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e20736f3fea1fa2ce7a01c692ee1ea62cbdc8770..c22cddc1e51af2fefb85c10a75f5d6f723fa5411"
+ "shas": "3c6ea542b73d4634a8ef1f3a4feab21638b44e59..7afddbc892244c8674ce4b38c15507863fff53ca"
}
,{
"testCaseDescription": "ruby-module-delete-replacement-test",
@@ -258,7 +258,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c22cddc1e51af2fefb85c10a75f5d6f723fa5411..ccf83dd52f2e34aad116fae51818e580f44a3dde"
+ "shas": "7afddbc892244c8674ce4b38c15507863fff53ca..b7bbbcc508c422b4015854ac411a5e8cb7f719d4"
}
,{
"testCaseDescription": "ruby-module-delete-test",
@@ -301,7 +301,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ccf83dd52f2e34aad116fae51818e580f44a3dde..1b1f8fe3b84a2ecbce6d55c673dfb72f1df307df"
+ "shas": "b7bbbcc508c422b4015854ac411a5e8cb7f719d4..f5ab4ccbd05717c316d09ee6f8b81ab07f9f2537"
}
,{
"testCaseDescription": "ruby-module-delete-rest-test",
@@ -342,5 +342,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1b1f8fe3b84a2ecbce6d55c673dfb72f1df307df..49b89941602d111543c0c41bd2bcb8a36aaa2bd2"
+ "shas": "f5ab4ccbd05717c316d09ee6f8b81ab07f9f2537..0bfd6502c8e772c64a20e5e6135cb4f76873567f"
}]
diff --git a/test/corpus/diff-summaries/ruby/multiple-assignments.json b/test/corpus/diff-summaries/ruby/multiple-assignments.json
index 856fd90cf..64888b83c 100644
--- a/test/corpus/diff-summaries/ruby/multiple-assignments.json
+++ b/test/corpus/diff-summaries/ruby/multiple-assignments.json
@@ -16,7 +16,7 @@
]
}
},
- "summary": "Added the 'identifier' assignment"
+ "summary": "Added the 'x, y, z' assignment"
}
]
},
@@ -34,7 +34,7 @@
"+x, y, z = [10, 20, 30]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f6e95f576fdbe837a5fa09bd74b0d87bcca7c856..190bd5e0997a27ffbdff88940136908640908c38"
+ "shas": "e18520c2388cc6132fcda418cd6e62396bb5efe3..255236fc9f81ac3fae7d989dcc91e54d07bfc6fb"
}
,{
"testCaseDescription": "ruby-multiple-assignments-replacement-insert-test",
@@ -54,7 +54,7 @@
]
}
},
- "summary": "Added the 'identifier' assignment"
+ "summary": "Added the 'x, y' assignment"
},
{
"span": {
@@ -69,7 +69,7 @@
]
}
},
- "summary": "Added the 'identifier' assignment"
+ "summary": "Added the 'x, y, z' assignment"
}
]
},
@@ -89,7 +89,7 @@
" x, y, z = [10, 20, 30]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "190bd5e0997a27ffbdff88940136908640908c38..da6c69115623e17dc7c8eb1304e0cc8e4964f069"
+ "shas": "255236fc9f81ac3fae7d989dcc91e54d07bfc6fb..5e9ddd7a6b85f6c1dc2bd7841fb1db3de7b59e84"
}
,{
"testCaseDescription": "ruby-multiple-assignments-delete-insert-test",
@@ -109,7 +109,7 @@
]
}
},
- "summary": "Added the 'y' identifier in an assignment to identifier"
+ "summary": "Added the 'y' identifier in an assignment to x, y, z"
},
{
"span": {
@@ -124,7 +124,7 @@
]
}
},
- "summary": "Added the 'z' identifier in an assignment to identifier"
+ "summary": "Added the 'z' identifier in an assignment to x, y, z"
},
{
"span": {
@@ -139,7 +139,7 @@
]
}
},
- "summary": "Deleted the 'y' identifier in an assignment to identifier"
+ "summary": "Deleted the 'y' identifier in an assignment to x, y, z"
}
]
},
@@ -160,7 +160,7 @@
" x, y, z = [10, 20, 30]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "da6c69115623e17dc7c8eb1304e0cc8e4964f069..b6afa3cdd73a6c210b364f036298e68565586e64"
+ "shas": "5e9ddd7a6b85f6c1dc2bd7841fb1db3de7b59e84..14e2a6b8224693360fb84cda66df6a7d6d7d15cf"
}
,{
"testCaseDescription": "ruby-multiple-assignments-replacement-test",
@@ -180,7 +180,7 @@
]
}
},
- "summary": "Added the 'y' identifier in an assignment to identifier"
+ "summary": "Added the 'y' identifier in an assignment to x, y"
},
{
"span": {
@@ -195,7 +195,7 @@
]
}
},
- "summary": "Deleted the 'y' identifier in an assignment to identifier"
+ "summary": "Deleted the 'y' identifier in an assignment to x, y"
},
{
"span": {
@@ -210,7 +210,7 @@
]
}
},
- "summary": "Deleted the 'z' identifier in an assignment to identifier"
+ "summary": "Deleted the 'z' identifier in an assignment to x, y"
}
]
},
@@ -231,7 +231,7 @@
" x, y, z = [10, 20, 30]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b6afa3cdd73a6c210b364f036298e68565586e64..227d94a55c4f5767d2acf64611ec8f7b43b1684b"
+ "shas": "14e2a6b8224693360fb84cda66df6a7d6d7d15cf..7d1e77bf88d20e8f53cf1c549983ba8d99ff5a85"
}
,{
"testCaseDescription": "ruby-multiple-assignments-delete-replacement-test",
@@ -251,7 +251,7 @@
]
}
},
- "summary": "Deleted the 'identifier' assignment"
+ "summary": "Deleted the 'x, y' assignment"
},
{
"span": {
@@ -266,7 +266,7 @@
]
}
},
- "summary": "Deleted the 'identifier' assignment"
+ "summary": "Deleted the 'x, y, z' assignment"
},
{
"span": {
@@ -281,7 +281,7 @@
]
}
},
- "summary": "Added the 'identifier' assignment"
+ "summary": "Added the 'x, y' assignment"
}
]
},
@@ -302,7 +302,7 @@
"+x, *y = [10, 20, 30]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "227d94a55c4f5767d2acf64611ec8f7b43b1684b..653a9966391e154a4118d956be4fbd034c2a6282"
+ "shas": "7d1e77bf88d20e8f53cf1c549983ba8d99ff5a85..5bfe819275a3c67fa4b7a9fcdd0eac050a3de8aa"
}
,{
"testCaseDescription": "ruby-multiple-assignments-delete-test",
@@ -322,7 +322,7 @@
]
}
},
- "summary": "Deleted the 'identifier' assignment"
+ "summary": "Deleted the 'x, y, z' assignment"
}
]
},
@@ -341,7 +341,7 @@
" x, *y = [10, 20, 30]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "653a9966391e154a4118d956be4fbd034c2a6282..1d61feafbd0c4da519a3e742e8a47d99baa7f596"
+ "shas": "5bfe819275a3c67fa4b7a9fcdd0eac050a3de8aa..c9093f1da853ac7a129b950ed0c5f8a22233621b"
}
,{
"testCaseDescription": "ruby-multiple-assignments-delete-rest-test",
@@ -361,7 +361,7 @@
]
}
},
- "summary": "Deleted the 'identifier' assignment"
+ "summary": "Deleted the 'x, y' assignment"
}
]
},
@@ -379,5 +379,5 @@
"-x, *y = [10, 20, 30]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1d61feafbd0c4da519a3e742e8a47d99baa7f596..c38d6e0fc468af7f3198dd33bc2163af92c8a859"
+ "shas": "c9093f1da853ac7a129b950ed0c5f8a22233621b..d92b06aee0d1f67da39bcc34fd6d9920da89f089"
}]
diff --git a/test/corpus/diff-summaries/ruby/number.json b/test/corpus/diff-summaries/ruby/number.json
index ab74da5a9..db8815aee 100644
--- a/test/corpus/diff-summaries/ruby/number.json
+++ b/test/corpus/diff-summaries/ruby/number.json
@@ -131,7 +131,7 @@
"+"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "102ebf0b263b96260e08b9e01bc647378aac78db..03046cb3bf4cbe31faf5cd4c356e0ac068ff9642"
+ "shas": "3345b250a3b074d0b3725cfa9ada030ac0733c03..b35c0ae4461db11b6bc1c00ce53aced00ee35f9f"
}
,{
"testCaseDescription": "ruby-number-replacement-insert-test",
@@ -409,7 +409,7 @@
" 0d1_234"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "03046cb3bf4cbe31faf5cd4c356e0ac068ff9642..c05d348f344ed0ef0a7cefe0d35e2b1419fdf0e9"
+ "shas": "b35c0ae4461db11b6bc1c00ce53aced00ee35f9f..722327896e7ef9a21676eca5e8eb6715e7401aa2"
}
,{
"testCaseDescription": "ruby-number-delete-insert-test",
@@ -658,7 +658,7 @@
" 1_234"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c05d348f344ed0ef0a7cefe0d35e2b1419fdf0e9..e6247d62ffbc30097496c2392976cc8455e32135"
+ "shas": "722327896e7ef9a21676eca5e8eb6715e7401aa2..d544881fc9626b821f44434f08e418475cf152de"
}
,{
"testCaseDescription": "ruby-number-replacement-test",
@@ -907,7 +907,7 @@
" 1_234"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e6247d62ffbc30097496c2392976cc8455e32135..8dd477881bd9d54252c0ff0392e9694a012d0559"
+ "shas": "d544881fc9626b821f44434f08e418475cf152de..67a6d066a1c1934842185072f8b4d14bed470dcd"
}
,{
"testCaseDescription": "ruby-number-delete-replacement-test",
@@ -1304,7 +1304,7 @@
" "
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8dd477881bd9d54252c0ff0392e9694a012d0559..513a1704a158d929abea327b8329e217728e9915"
+ "shas": "67a6d066a1c1934842185072f8b4d14bed470dcd..c4ebf6bf580826410bf6f43b1cddb603f489e60f"
}
,{
"testCaseDescription": "ruby-number-delete-test",
@@ -1472,7 +1472,7 @@
" 0d1_235"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "513a1704a158d929abea327b8329e217728e9915..b7535ab7400416911cc620f08e5b1d450efa9c50"
+ "shas": "c4ebf6bf580826410bf6f43b1cddb603f489e60f..2ff54d83dfd80eba661e8a5c4c7ed2b61d289e87"
}
,{
"testCaseDescription": "ruby-number-delete-rest-test",
@@ -1607,5 +1607,5 @@
"-"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b7535ab7400416911cc620f08e5b1d450efa9c50..e1f12c295c3380e860cce36493b9639e688eb056"
+ "shas": "2ff54d83dfd80eba661e8a5c4c7ed2b61d289e87..5063a6e97353e552c8a9a38f3cf69ef68790c3ab"
}]
diff --git a/test/corpus/diff-summaries/ruby/percent-array.json b/test/corpus/diff-summaries/ruby/percent-array.json
index 408cee605..bfc4582aa 100644
--- a/test/corpus/diff-summaries/ruby/percent-array.json
+++ b/test/corpus/diff-summaries/ruby/percent-array.json
@@ -34,7 +34,7 @@
"+%w(one two)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "793e1bdbe7ec874e9b83489ff39233476953a8f8..15b317c93ed35622c3a7fe384fbfad8b076d3bb7"
+ "shas": "50239ae63445ee12774182b323b735f392bdacdf..a7e3abb247fb7745756dbddf2308729399f71ef4"
}
,{
"testCaseDescription": "ruby-percent-array-replacement-insert-test",
@@ -89,7 +89,7 @@
" %w(one two)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "15b317c93ed35622c3a7fe384fbfad8b076d3bb7..f144cb1cf8e1795d34b35e6ce317c284d00376eb"
+ "shas": "a7e3abb247fb7745756dbddf2308729399f71ef4..e88a9b1d3365387c6fb8441bb04c0825192094c7"
}
,{
"testCaseDescription": "ruby-percent-array-delete-insert-test",
@@ -130,7 +130,7 @@
" %w(one two)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f144cb1cf8e1795d34b35e6ce317c284d00376eb..857fd2946cb46b9a08edab28e5cf198c742bfa11"
+ "shas": "e88a9b1d3365387c6fb8441bb04c0825192094c7..f8d2dfe3f1ffef4408e4048d6c0e6fe56c840999"
}
,{
"testCaseDescription": "ruby-percent-array-replacement-test",
@@ -171,7 +171,7 @@
" %w(one two)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "857fd2946cb46b9a08edab28e5cf198c742bfa11..dea32425b07fe0f468437448a9405a27e1e9feb9"
+ "shas": "f8d2dfe3f1ffef4408e4048d6c0e6fe56c840999..2ee908509e74e7d42ec52ca757f059011679a894"
}
,{
"testCaseDescription": "ruby-percent-array-delete-replacement-test",
@@ -242,7 +242,7 @@
"+%W(one #{b} three)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "dea32425b07fe0f468437448a9405a27e1e9feb9..6e7a5ff793203d4b44da87556a5ae0aeaf92d381"
+ "shas": "2ee908509e74e7d42ec52ca757f059011679a894..d997f76ec24b13f760a5c47f43fffb07a3ada7f5"
}
,{
"testCaseDescription": "ruby-percent-array-delete-test",
@@ -281,7 +281,7 @@
" %W(one #{b} three)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6e7a5ff793203d4b44da87556a5ae0aeaf92d381..7a4736498b7c31e5ddeaff932060b456bbd9eabb"
+ "shas": "d997f76ec24b13f760a5c47f43fffb07a3ada7f5..4847fda42bb24f9729ada1a5bbfd42820728496b"
}
,{
"testCaseDescription": "ruby-percent-array-delete-rest-test",
@@ -319,5 +319,5 @@
"-%W(one #{b} three)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7a4736498b7c31e5ddeaff932060b456bbd9eabb..6c8dc9471a192b2a2dbb0003b78e81330f92875e"
+ "shas": "4847fda42bb24f9729ada1a5bbfd42820728496b..0caec37a9c91cd2e743845adbd4fd52f27f01026"
}]
diff --git a/test/corpus/diff-summaries/ruby/pseudo-variables.json b/test/corpus/diff-summaries/ruby/pseudo-variables.json
index 0d2e7841f..481d4171c 100644
--- a/test/corpus/diff-summaries/ruby/pseudo-variables.json
+++ b/test/corpus/diff-summaries/ruby/pseudo-variables.json
@@ -82,7 +82,7 @@
"+true"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c38d6e0fc468af7f3198dd33bc2163af92c8a859..8d7efc33cee1f7e9f54b9dfb1adb4bf46353205a"
+ "shas": "d92b06aee0d1f67da39bcc34fd6d9920da89f089..f244146cbbeac71aca6818420638059664e3b957"
}
,{
"testCaseDescription": "ruby-pseudo-variables-replacement-insert-test",
@@ -235,7 +235,7 @@
" false"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8d7efc33cee1f7e9f54b9dfb1adb4bf46353205a..649761e4e50ea33572c1d83db7510038864e90ce"
+ "shas": "f244146cbbeac71aca6818420638059664e3b957..824d7890359e99e81b998602857443393e4904c9"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-insert-test",
@@ -354,7 +354,7 @@
" false"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "649761e4e50ea33572c1d83db7510038864e90ce..43ff2336cfc3898dd7240c85eb4c4aff6100b052"
+ "shas": "824d7890359e99e81b998602857443393e4904c9..062d0836ac07fbc74685c09d4d916aef763f34a7"
}
,{
"testCaseDescription": "ruby-pseudo-variables-replacement-test",
@@ -473,7 +473,7 @@
" false"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "43ff2336cfc3898dd7240c85eb4c4aff6100b052..85b0a7d2d2a591a338e16033a75fec3b16ee7fd8"
+ "shas": "062d0836ac07fbc74685c09d4d916aef763f34a7..04c0c35bce1d6642f0a70556fdb8593e94c6d028"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-replacement-test",
@@ -660,7 +660,7 @@
"+FALSE"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "85b0a7d2d2a591a338e16033a75fec3b16ee7fd8..fe6068b8633ac994123f3fc38b5e410094c4dd81"
+ "shas": "04c0c35bce1d6642f0a70556fdb8593e94c6d028..836b5f1a139aa3d483680a636e593f9728fd96e8"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-test",
@@ -749,7 +749,7 @@
" TRUE"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fe6068b8633ac994123f3fc38b5e410094c4dd81..fb5d62632742963414e39827696e7f7fd922438f"
+ "shas": "836b5f1a139aa3d483680a636e593f9728fd96e8..30c34d8542d694db1efe435710ee53196e0f4ab7"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-rest-test",
@@ -835,5 +835,5 @@
"-FALSE"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fb5d62632742963414e39827696e7f7fd922438f..f52d3de2a15d5d30f50d3567a63f7fb2ae586de8"
+ "shas": "30c34d8542d694db1efe435710ee53196e0f4ab7..37466370f19570447f01519a8c892afd6ced7df8"
}]
diff --git a/test/corpus/diff-summaries/ruby/regex.json b/test/corpus/diff-summaries/ruby/regex.json
index 64206bf5f..0acb1b2c7 100644
--- a/test/corpus/diff-summaries/ruby/regex.json
+++ b/test/corpus/diff-summaries/ruby/regex.json
@@ -34,7 +34,7 @@
"+/^(foo|bar[^_])$/i"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "276112ad3f93ee93fa30985c16b91d38d36f4e32..6aaa07924506f69f8522086d196e35b08343eb18"
+ "shas": "72d6e4e549ce17f88e6130002ccc0ecd6302fdf2..c3d9695417e6678a456a6692f3f708f3578a9cf2"
}
,{
"testCaseDescription": "ruby-regex-replacement-insert-test",
@@ -87,7 +87,7 @@
" /^(foo|bar[^_])$/i"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6aaa07924506f69f8522086d196e35b08343eb18..9f00010da24ed0d086128636c800de0f08653c00"
+ "shas": "c3d9695417e6678a456a6692f3f708f3578a9cf2..390ab71fc475ff76aa74e63dc827efa8d620fd7c"
}
,{
"testCaseDescription": "ruby-regex-delete-insert-test",
@@ -141,7 +141,7 @@
" /^(foo|bar[^_])$/i"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9f00010da24ed0d086128636c800de0f08653c00..919b19cd1bf9f48ad33b76631241cbe98ceecec3"
+ "shas": "390ab71fc475ff76aa74e63dc827efa8d620fd7c..226f8b30f81ea0db57e79e1212adfc07130c6872"
}
,{
"testCaseDescription": "ruby-regex-replacement-test",
@@ -195,7 +195,7 @@
" /^(foo|bar[^_])$/i"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "919b19cd1bf9f48ad33b76631241cbe98ceecec3..f259434fbe33c263524e528a5f7f8f6c924de20e"
+ "shas": "226f8b30f81ea0db57e79e1212adfc07130c6872..b8e98f854bb60e2823c562708c8ac5a4d4668d1e"
}
,{
"testCaseDescription": "ruby-regex-delete-replacement-test",
@@ -249,7 +249,7 @@
"-/^(foo|bar[^_])$/i"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f259434fbe33c263524e528a5f7f8f6c924de20e..558e8e07425e316becc1a93aa1dacd749dbe35f3"
+ "shas": "b8e98f854bb60e2823c562708c8ac5a4d4668d1e..e9466dc38a6269d4defca09ae238272e8b593087"
}
,{
"testCaseDescription": "ruby-regex-delete-test",
@@ -289,7 +289,7 @@
" %r c>"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "558e8e07425e316becc1a93aa1dacd749dbe35f3..88fb96f4ab7f7464bdd51e95f495ca8752bcd6f7"
+ "shas": "e9466dc38a6269d4defca09ae238272e8b593087..5f3afced7715c5a7e7454ccf1817f4f3450def9f"
}
,{
"testCaseDescription": "ruby-regex-delete-rest-test",
@@ -346,5 +346,5 @@
"-%r c>"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "88fb96f4ab7f7464bdd51e95f495ca8752bcd6f7..c05b5a765cdcea2458b77acf718ccf2623e578fa"
+ "shas": "5f3afced7715c5a7e7454ccf1817f4f3450def9f..38a4fc97908a2d22a188038b11a90fee2a3326eb"
}]
diff --git a/test/corpus/diff-summaries/ruby/relational-operator.json b/test/corpus/diff-summaries/ruby/relational-operator.json
index 682ddab5f..381fde069 100644
--- a/test/corpus/diff-summaries/ruby/relational-operator.json
+++ b/test/corpus/diff-summaries/ruby/relational-operator.json
@@ -66,7 +66,7 @@
"+x === y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5a6d083875f84d691932dcce0fc121fdc3a56264..aaebedced80e13522e59242435d1ae108d83d588"
+ "shas": "6c27e99fb23d5f85525e0885c8e8a54cbfc8717a..e0a04c14d081fc4af4d0be4e9bf605b0f7d6a7a7"
}
,{
"testCaseDescription": "ruby-relational-operator-replacement-insert-test",
@@ -187,7 +187,7 @@
" x === y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "aaebedced80e13522e59242435d1ae108d83d588..e3d8e622e2afbfcca355740550537ce94d65a4a7"
+ "shas": "e0a04c14d081fc4af4d0be4e9bf605b0f7d6a7a7..5501c6d757aa15bc44b996da2f7feda03d982c9a"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-insert-test",
@@ -302,7 +302,7 @@
" x === y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e3d8e622e2afbfcca355740550537ce94d65a4a7..e7f396d82dce8fa34b838955e23abaab7cf4ee8a"
+ "shas": "5501c6d757aa15bc44b996da2f7feda03d982c9a..bc3940d03248483f5a5ded1154da28bafdd61e6d"
}
,{
"testCaseDescription": "ruby-relational-operator-replacement-test",
@@ -417,7 +417,7 @@
" x === y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e7f396d82dce8fa34b838955e23abaab7cf4ee8a..59601d462e8aff32014804b3c547e72acf198bd0"
+ "shas": "bc3940d03248483f5a5ded1154da28bafdd61e6d..845f97666626d2b7096a0f24436fba8256aaedb2"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-replacement-test",
@@ -586,7 +586,7 @@
"+x =! y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "59601d462e8aff32014804b3c547e72acf198bd0..3a739f7a9609044fe0a34f2d3fc6032791889363"
+ "shas": "845f97666626d2b7096a0f24436fba8256aaedb2..50883312aabe25d9afc9c4c50aa9d65ad3f7bc21"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-test",
@@ -659,7 +659,7 @@
" x =! y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3a739f7a9609044fe0a34f2d3fc6032791889363..a9e49b19cf82ef69d5dac01c950a881efdc7d63a"
+ "shas": "50883312aabe25d9afc9c4c50aa9d65ad3f7bc21..4390aecfa9191d7b213eec2c3e32890670f4742b"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-rest-test",
@@ -729,5 +729,5 @@
"-x =! y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a9e49b19cf82ef69d5dac01c950a881efdc7d63a..8b0ce2b5b84158c85e605ab2a0073b9b89994fed"
+ "shas": "4390aecfa9191d7b213eec2c3e32890670f4742b..1b803e056a1487ac155e74204ddaa92b7fd30c5b"
}]
diff --git a/test/corpus/diff-summaries/ruby/rescue-empty.json b/test/corpus/diff-summaries/ruby/rescue-empty.json
index a1e2ccef2..524831be0 100644
--- a/test/corpus/diff-summaries/ruby/rescue-empty.json
+++ b/test/corpus/diff-summaries/ruby/rescue-empty.json
@@ -37,7 +37,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a54b44d243fc9c9b17f57c8f0f8dd6cb863e379a..a116d9dbf03f1abf7eace12de27039bc22e1ce0c"
+ "shas": "f47b92e170f4e1804220849365a39277184fb02c..b9047fff4793731e95f70f6cb7e62b9cc663d0f7"
}
,{
"testCaseDescription": "ruby-rescue-empty-replacement-insert-test",
@@ -102,7 +102,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a116d9dbf03f1abf7eace12de27039bc22e1ce0c..a523108d33307743d7a836a2694237ed45028f9f"
+ "shas": "b9047fff4793731e95f70f6cb7e62b9cc663d0f7..a6db02dac39030485ba11c4ef87b687122387849"
}
,{
"testCaseDescription": "ruby-rescue-empty-delete-insert-test",
@@ -146,7 +146,7 @@
" foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a523108d33307743d7a836a2694237ed45028f9f..a515cdc8d24b637efbeec610dc60c7521cfa528c"
+ "shas": "a6db02dac39030485ba11c4ef87b687122387849..d8613eca595b18ae2652efa14e08043a694e3e90"
}
,{
"testCaseDescription": "ruby-rescue-empty-replacement-test",
@@ -190,7 +190,7 @@
" foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a515cdc8d24b637efbeec610dc60c7521cfa528c..83e6882400cdde2468f6ab42d673da0ffcccc77e"
+ "shas": "d8613eca595b18ae2652efa14e08043a694e3e90..24e33db9fb593949652559dd7a11fbcaa347f1fc"
}
,{
"testCaseDescription": "ruby-rescue-empty-delete-replacement-test",
@@ -271,7 +271,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "83e6882400cdde2468f6ab42d673da0ffcccc77e..bf3671a81a3621192799f723781073b4b97dff96"
+ "shas": "24e33db9fb593949652559dd7a11fbcaa347f1fc..3a74386d964969e2a9ef1bed038700f0f1f10b3c"
}
,{
"testCaseDescription": "ruby-rescue-empty-delete-test",
@@ -317,7 +317,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "bf3671a81a3621192799f723781073b4b97dff96..02d083771ed4db0db4da6503b9b7674cd8e0501b"
+ "shas": "3a74386d964969e2a9ef1bed038700f0f1f10b3c..aa2c856f7e4b392a3483a7b95e25c1d712ae4d65"
}
,{
"testCaseDescription": "ruby-rescue-empty-delete-rest-test",
@@ -359,5 +359,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "02d083771ed4db0db4da6503b9b7674cd8e0501b..35faaef8a55784bfa78c1d05992dad26c2a4f09c"
+ "shas": "aa2c856f7e4b392a3483a7b95e25c1d712ae4d65..9d9a8b8a5df678511e5d7e4325486b750961ce62"
}]
diff --git a/test/corpus/diff-summaries/ruby/rescue-last-ex.json b/test/corpus/diff-summaries/ruby/rescue-last-ex.json
index 9f22f99de..57d31defe 100644
--- a/test/corpus/diff-summaries/ruby/rescue-last-ex.json
+++ b/test/corpus/diff-summaries/ruby/rescue-last-ex.json
@@ -37,7 +37,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "35faaef8a55784bfa78c1d05992dad26c2a4f09c..2556916a890d34d69105e5a0ae6db7cc18033ec1"
+ "shas": "9d9a8b8a5df678511e5d7e4325486b750961ce62..1c49b68e50506f83dd1ed4d7a735d1dc5aaf14fe"
}
,{
"testCaseDescription": "ruby-rescue-last-ex-replacement-insert-test",
@@ -102,7 +102,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2556916a890d34d69105e5a0ae6db7cc18033ec1..4dccfecc2b088adc6873334a3404fe0da39a610d"
+ "shas": "1c49b68e50506f83dd1ed4d7a735d1dc5aaf14fe..835642904ada16ab614d7eb214a36a26fc4d0fd9"
}
,{
"testCaseDescription": "ruby-rescue-last-ex-delete-insert-test",
@@ -122,7 +122,7 @@
]
}
},
- "summary": "Deleted the 'bar' identifier in the 'Error, identifier' rescue block"
+ "summary": "Deleted the 'bar' identifier in the 'Error, x' rescue block"
}
]
},
@@ -146,7 +146,7 @@
" foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4dccfecc2b088adc6873334a3404fe0da39a610d..e1f61e94d975de70d1455649be34f351588a738d"
+ "shas": "835642904ada16ab614d7eb214a36a26fc4d0fd9..4cc838a5be5770ae973653cb06e7f70d50e81a18"
}
,{
"testCaseDescription": "ruby-rescue-last-ex-replacement-test",
@@ -166,7 +166,7 @@
]
}
},
- "summary": "Added the 'bar' identifier in the 'Error, identifier' rescue block"
+ "summary": "Added the 'bar' identifier in the 'Error, x' rescue block"
}
]
},
@@ -190,7 +190,7 @@
" foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e1f61e94d975de70d1455649be34f351588a738d..26d3942e47b5fd260ce2f0b8535e0b084405ed1d"
+ "shas": "4cc838a5be5770ae973653cb06e7f70d50e81a18..6ef28ff9d622104d06fe32c0a35681c866d7fc09"
}
,{
"testCaseDescription": "ruby-rescue-last-ex-delete-replacement-test",
@@ -271,7 +271,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "26d3942e47b5fd260ce2f0b8535e0b084405ed1d..90339c0f03a65703a253740b0cf0b1d9af0225e0"
+ "shas": "6ef28ff9d622104d06fe32c0a35681c866d7fc09..6c0996f584253d460b227145d743131dbb18cc07"
}
,{
"testCaseDescription": "ruby-rescue-last-ex-delete-test",
@@ -317,7 +317,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "90339c0f03a65703a253740b0cf0b1d9af0225e0..03acd387c2a93e02abfb7eb00cc02d93963fadd1"
+ "shas": "6c0996f584253d460b227145d743131dbb18cc07..d98b28af01727259ee6d6644d03c9a2f76d123e8"
}
,{
"testCaseDescription": "ruby-rescue-last-ex-delete-rest-test",
@@ -359,5 +359,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "03acd387c2a93e02abfb7eb00cc02d93963fadd1..9f69fa5b922d67f8be375f290985dd2088dcee60"
+ "shas": "d98b28af01727259ee6d6644d03c9a2f76d123e8..a0ed35994c68819d5a0f68519e2cde978618e201"
}]
diff --git a/test/corpus/diff-summaries/ruby/rescue-modifier.json b/test/corpus/diff-summaries/ruby/rescue-modifier.json
index 39199a2ad..f794f40ff 100644
--- a/test/corpus/diff-summaries/ruby/rescue-modifier.json
+++ b/test/corpus/diff-summaries/ruby/rescue-modifier.json
@@ -34,7 +34,7 @@
"+foo rescue nil"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9f69fa5b922d67f8be375f290985dd2088dcee60..a7b03258b36def8f150d825d81e31d3472f6c9ca"
+ "shas": "a0ed35994c68819d5a0f68519e2cde978618e201..78a95cb2a90457e4cc7ab609fc45ef4ccbb2cb5b"
}
,{
"testCaseDescription": "ruby-rescue-modifier-replacement-insert-test",
@@ -89,7 +89,7 @@
" foo rescue nil"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a7b03258b36def8f150d825d81e31d3472f6c9ca..dcafb17d81b4e9cb9c02334f598aaeb4d038dca1"
+ "shas": "78a95cb2a90457e4cc7ab609fc45ef4ccbb2cb5b..525f4e27a42206352f921ff1af2e4a19ffa02885"
}
,{
"testCaseDescription": "ruby-rescue-modifier-delete-insert-test",
@@ -142,7 +142,7 @@
" foo rescue nil"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "dcafb17d81b4e9cb9c02334f598aaeb4d038dca1..47881adb97db7494b965f891077ca41aa0d7f29d"
+ "shas": "525f4e27a42206352f921ff1af2e4a19ffa02885..90e7b2da0567b511245749fd5744f326d97be093"
}
,{
"testCaseDescription": "ruby-rescue-modifier-replacement-test",
@@ -195,7 +195,7 @@
" foo rescue nil"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "47881adb97db7494b965f891077ca41aa0d7f29d..6c6f736fa631ad8899be0689ed2d35bf5402b055"
+ "shas": "90e7b2da0567b511245749fd5744f326d97be093..e7a36c7bb7dce30fd5e9105ff911da3186774a14"
}
,{
"testCaseDescription": "ruby-rescue-modifier-delete-replacement-test",
@@ -266,7 +266,7 @@
"+foo rescue false"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6c6f736fa631ad8899be0689ed2d35bf5402b055..319065260ac33119323c64bff11b1bce34de0414"
+ "shas": "e7a36c7bb7dce30fd5e9105ff911da3186774a14..2a452ccd83457c1261298ebadf13e1de3ca73c5a"
}
,{
"testCaseDescription": "ruby-rescue-modifier-delete-test",
@@ -305,7 +305,7 @@
" foo rescue false"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "319065260ac33119323c64bff11b1bce34de0414..f04a9f76800e2b14705b685a01523c7f89cc3a7a"
+ "shas": "2a452ccd83457c1261298ebadf13e1de3ca73c5a..dbef0d415d1ee73442667e820376938e35879598"
}
,{
"testCaseDescription": "ruby-rescue-modifier-delete-rest-test",
@@ -343,5 +343,5 @@
"-foo rescue false"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f04a9f76800e2b14705b685a01523c7f89cc3a7a..b16575bbac31d76c5030dfe7a60b4a4311708f37"
+ "shas": "dbef0d415d1ee73442667e820376938e35879598..e9c1b799bbc4ee90223e122dda29e0f364b52f22"
}]
diff --git a/test/corpus/diff-summaries/ruby/rescue-modifier2.json b/test/corpus/diff-summaries/ruby/rescue-modifier2.json
index 411510ee3..b806c1b58 100644
--- a/test/corpus/diff-summaries/ruby/rescue-modifier2.json
+++ b/test/corpus/diff-summaries/ruby/rescue-modifier2.json
@@ -34,7 +34,7 @@
"+foo rescue nil"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b16575bbac31d76c5030dfe7a60b4a4311708f37..840befdc4e06589c43895c8db737637a97461b3c"
+ "shas": "e9c1b799bbc4ee90223e122dda29e0f364b52f22..e81ba866671447ff7bc5f1f24a7f3e91f49ea964"
}
,{
"testCaseDescription": "ruby-rescue-modifier2-replacement-insert-test",
@@ -89,7 +89,7 @@
" foo rescue nil"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "840befdc4e06589c43895c8db737637a97461b3c..99c235875aff1b7b311b39f42981800c93b15d49"
+ "shas": "e81ba866671447ff7bc5f1f24a7f3e91f49ea964..92c9e0bc99fb7fb0e612ed09714cbdb450136f4a"
}
,{
"testCaseDescription": "ruby-rescue-modifier2-delete-insert-test",
@@ -142,7 +142,7 @@
" foo rescue nil"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "99c235875aff1b7b311b39f42981800c93b15d49..b7c7d61c088d4853b34a977c4878425d434e0bbe"
+ "shas": "92c9e0bc99fb7fb0e612ed09714cbdb450136f4a..cf55e64d84e27a6376c1205bc1b21e7543913f6f"
}
,{
"testCaseDescription": "ruby-rescue-modifier2-replacement-test",
@@ -195,7 +195,7 @@
" foo rescue nil"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b7c7d61c088d4853b34a977c4878425d434e0bbe..aaea52953033281fa84804eeb327a97553dd0a9d"
+ "shas": "cf55e64d84e27a6376c1205bc1b21e7543913f6f..1338e35da36781bf633429cdf1ea5466f95d723f"
}
,{
"testCaseDescription": "ruby-rescue-modifier2-delete-replacement-test",
@@ -266,7 +266,7 @@
"+bar rescue nil"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "aaea52953033281fa84804eeb327a97553dd0a9d..e19593638626629c8b76aa27120f74b303203d18"
+ "shas": "1338e35da36781bf633429cdf1ea5466f95d723f..1329bef2b2836bddb1d7d7aa232c2ab50d51ea49"
}
,{
"testCaseDescription": "ruby-rescue-modifier2-delete-test",
@@ -305,7 +305,7 @@
" bar rescue nil"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e19593638626629c8b76aa27120f74b303203d18..eabee37ca539e90e034aac90683bbaa1206309da"
+ "shas": "1329bef2b2836bddb1d7d7aa232c2ab50d51ea49..09e75845712a601fd0a6b85e480c9d3c6c0f9d83"
}
,{
"testCaseDescription": "ruby-rescue-modifier2-delete-rest-test",
@@ -343,5 +343,5 @@
"-bar rescue nil"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "eabee37ca539e90e034aac90683bbaa1206309da..0f3ddff0899d7aea39733b5f21639fca68bd0b51"
+ "shas": "09e75845712a601fd0a6b85e480c9d3c6c0f9d83..d7c0d9f3779b10092fd36936b786ecb673cc2cc8"
}]
diff --git a/test/corpus/diff-summaries/ruby/rescue.json b/test/corpus/diff-summaries/ruby/rescue.json
index b483237aa..8f0c80b43 100644
--- a/test/corpus/diff-summaries/ruby/rescue.json
+++ b/test/corpus/diff-summaries/ruby/rescue.json
@@ -36,7 +36,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5cc243cda94fa2788a86c16754a39ec988628dbb..0338002e6bd03e54140e964585ddec6d19e8bdff"
+ "shas": "3ed4858d0df31fefc47cf20d5f24390fd8aad9ce..dfa7123607968ba0f71a44b2db3c6f003392c189"
}
,{
"testCaseDescription": "ruby-rescue-insert-test",
@@ -77,7 +77,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0338002e6bd03e54140e964585ddec6d19e8bdff..0ba3e468d7a0c33d9c81f6f284091a5746d69371"
+ "shas": "dfa7123607968ba0f71a44b2db3c6f003392c189..26d0443f2c570cae7488b43c70d188072bd3fde8"
}
,{
"testCaseDescription": "ruby-rescue-replacement-test",
@@ -119,7 +119,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0ba3e468d7a0c33d9c81f6f284091a5746d69371..f8bb5f00f89c00ddb27880df59891a5440e1e954"
+ "shas": "26d0443f2c570cae7488b43c70d188072bd3fde8..3e68cfc45cb218de3bc4a39a333331dadd8892d7"
}
,{
"testCaseDescription": "ruby-rescue-delete-replacement-test",
@@ -161,7 +161,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f8bb5f00f89c00ddb27880df59891a5440e1e954..e3923cd1f2fd5e0198052b4bab0da5280aeb5a9f"
+ "shas": "3e68cfc45cb218de3bc4a39a333331dadd8892d7..ee5b4eea19f45f9787e30dc4c36f0a4a3c3c07ea"
}
,{
"testCaseDescription": "ruby-rescue-delete-insert-test",
@@ -202,7 +202,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e3923cd1f2fd5e0198052b4bab0da5280aeb5a9f..49a0e672bacd6e1af361828f67b5490e31d5e67f"
+ "shas": "ee5b4eea19f45f9787e30dc4c36f0a4a3c3c07ea..015d7d0c2c3e6af6da1591d3425a2d1229dba62f"
}
,{
"testCaseDescription": "ruby-rescue-teardown-test",
@@ -242,5 +242,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "49a0e672bacd6e1af361828f67b5490e31d5e67f..a54b44d243fc9c9b17f57c8f0f8dd6cb863e379a"
+ "shas": "015d7d0c2c3e6af6da1591d3425a2d1229dba62f..f47b92e170f4e1804220849365a39277184fb02c"
}]
diff --git a/test/corpus/diff-summaries/ruby/return.json b/test/corpus/diff-summaries/ruby/return.json
index 08f5e7c62..207841b29 100644
--- a/test/corpus/diff-summaries/ruby/return.json
+++ b/test/corpus/diff-summaries/ruby/return.json
@@ -34,7 +34,7 @@
"+return foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "49b89941602d111543c0c41bd2bcb8a36aaa2bd2..ae4cb5a28a74d0929c33e3f2e82fd772aa841e20"
+ "shas": "0bfd6502c8e772c64a20e5e6135cb4f76873567f..1803bc99eda2db60140c51bfc1bddad40891220d"
}
,{
"testCaseDescription": "ruby-return-replacement-insert-test",
@@ -89,7 +89,7 @@
" return foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ae4cb5a28a74d0929c33e3f2e82fd772aa841e20..de7d46e3fc38fcd199fe1d8742edcb4d67c87ea6"
+ "shas": "1803bc99eda2db60140c51bfc1bddad40891220d..d7e5e4e466481b9b90342c9c8aa7af11c8eb263f"
}
,{
"testCaseDescription": "ruby-return-delete-insert-test",
@@ -130,7 +130,7 @@
" return foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "de7d46e3fc38fcd199fe1d8742edcb4d67c87ea6..f1ff50b8366b2db33f84c97db09062706be25327"
+ "shas": "d7e5e4e466481b9b90342c9c8aa7af11c8eb263f..d6d850e5de1091fa05cbcc63e316f6ade073e1fc"
}
,{
"testCaseDescription": "ruby-return-replacement-test",
@@ -171,7 +171,7 @@
" return foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f1ff50b8366b2db33f84c97db09062706be25327..d12c3e5b152839e0d37f0cbcaf0070bb1ed7ee4e"
+ "shas": "d6d850e5de1091fa05cbcc63e316f6ade073e1fc..d5fe06579123a021eca62a49125bbf90ad075235"
}
,{
"testCaseDescription": "ruby-return-delete-replacement-test",
@@ -242,7 +242,7 @@
"+return"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d12c3e5b152839e0d37f0cbcaf0070bb1ed7ee4e..554a178c9cebedd8f260a46d16bab3528068f3e5"
+ "shas": "d5fe06579123a021eca62a49125bbf90ad075235..1adc01f2170612ba78dfcf3ef6cd7c12ae2d03f4"
}
,{
"testCaseDescription": "ruby-return-delete-test",
@@ -281,7 +281,7 @@
" return"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "554a178c9cebedd8f260a46d16bab3528068f3e5..fa3bd3293ca17ad5a5e2a8778d3593c7b0013484"
+ "shas": "1adc01f2170612ba78dfcf3ef6cd7c12ae2d03f4..6efdac1f13207bd957ec8aca0f37382eb0c1d54c"
}
,{
"testCaseDescription": "ruby-return-delete-rest-test",
@@ -319,5 +319,5 @@
"-return"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fa3bd3293ca17ad5a5e2a8778d3593c7b0013484..a60beed250baf3ff01e9f1d71d51d1eee16b3d18"
+ "shas": "6efdac1f13207bd957ec8aca0f37382eb0c1d54c..993b27aaf14a84e2d2f4f4d648b4c9c32e3b2378"
}]
diff --git a/test/corpus/diff-summaries/ruby/string.json b/test/corpus/diff-summaries/ruby/string.json
index 5c283ee9f..53dbf1baf 100644
--- a/test/corpus/diff-summaries/ruby/string.json
+++ b/test/corpus/diff-summaries/ruby/string.json
@@ -50,7 +50,7 @@
"+'foo with \"bar\"'"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c7a08a472303d6496e690e52bc239579bf99ef22..f05828087c1a703e1a587a7083445dc536dfd436"
+ "shas": "7882bb5b3e1cea5c33c4c86cf4a7935c534cf40c..03fa7d50b812e3f8d2b0aa2eafd90ef69acc8d47"
}
,{
"testCaseDescription": "ruby-string-replacement-insert-test",
@@ -138,7 +138,7 @@
" 'foo with \"bar\"'"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f05828087c1a703e1a587a7083445dc536dfd436..1bba1edeb28889267169649cea414cd5467f0d17"
+ "shas": "03fa7d50b812e3f8d2b0aa2eafd90ef69acc8d47..8fd6d9cbe0d5d8095fdd738d2992a615854f8279"
}
,{
"testCaseDescription": "ruby-string-delete-insert-test",
@@ -221,7 +221,7 @@
" ''"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1bba1edeb28889267169649cea414cd5467f0d17..916082d47bd0b6c51adfb3c63b0898c26b9cd852"
+ "shas": "8fd6d9cbe0d5d8095fdd738d2992a615854f8279..d245920a38a962ed509d75ab43a37ad62e770fea"
}
,{
"testCaseDescription": "ruby-string-replacement-test",
@@ -304,7 +304,7 @@
" ''"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "916082d47bd0b6c51adfb3c63b0898c26b9cd852..3951e63175b20cc2da877aa772d555a4d2d06e65"
+ "shas": "d245920a38a962ed509d75ab43a37ad62e770fea..243a4e119f2436f194abaa67832dbf350f4b5e9c"
}
,{
"testCaseDescription": "ruby-string-delete-replacement-test",
@@ -424,7 +424,7 @@
"+\"bar with 'foo'\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3951e63175b20cc2da877aa772d555a4d2d06e65..22425052c34385c8595bbf5031715bb549ad1b6c"
+ "shas": "243a4e119f2436f194abaa67832dbf350f4b5e9c..ea734be9988e2b130941727b78d975faa4288f2a"
}
,{
"testCaseDescription": "ruby-string-delete-test",
@@ -480,7 +480,7 @@
" \"bar with 'foo'\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "22425052c34385c8595bbf5031715bb549ad1b6c..4af78d51da5670974c0ec153e701ffe346a11847"
+ "shas": "ea734be9988e2b130941727b78d975faa4288f2a..df5d921acf65e2cbf45fad7a7971df78971c4b39"
}
,{
"testCaseDescription": "ruby-string-delete-rest-test",
@@ -534,5 +534,5 @@
"-\"bar with 'foo'\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4af78d51da5670974c0ec153e701ffe346a11847..7d1d1ea962e005a0b1ed1d2dc9a165478d2aa972"
+ "shas": "df5d921acf65e2cbf45fad7a7971df78971c4b39..ef0883c98e45e316c23578fc4159905d0093fd66"
}]
diff --git a/test/corpus/diff-summaries/ruby/subshell.json b/test/corpus/diff-summaries/ruby/subshell.json
index 6c106af94..30fc91d01 100644
--- a/test/corpus/diff-summaries/ruby/subshell.json
+++ b/test/corpus/diff-summaries/ruby/subshell.json
@@ -34,7 +34,7 @@
"+`ls -la`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f52d3de2a15d5d30f50d3567a63f7fb2ae586de8..313c1708ad1b8684b25e4666a539c10827018d44"
+ "shas": "37466370f19570447f01519a8c892afd6ced7df8..1bf98e4388e2ad3e9c34c809b5ca832225322d10"
}
,{
"testCaseDescription": "ruby-subshell-replacement-insert-test",
@@ -89,7 +89,7 @@
" `ls -la`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "313c1708ad1b8684b25e4666a539c10827018d44..b22683b8f113d01a1bef24902084fd0fff2f9377"
+ "shas": "1bf98e4388e2ad3e9c34c809b5ca832225322d10..33fa9117db15ae917eed0a1b1c8ca7ddbe34c34b"
}
,{
"testCaseDescription": "ruby-subshell-delete-insert-test",
@@ -142,7 +142,7 @@
" `ls -la`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b22683b8f113d01a1bef24902084fd0fff2f9377..376a5de1d61958be6e086597c60f8891560125bd"
+ "shas": "33fa9117db15ae917eed0a1b1c8ca7ddbe34c34b..557c25df0051a3b1cc5eef17e6b5672ec8cb2f05"
}
,{
"testCaseDescription": "ruby-subshell-replacement-test",
@@ -195,7 +195,7 @@
" `ls -la`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "376a5de1d61958be6e086597c60f8891560125bd..3614169030bf27a1ac6f8f23939e4fdd62e23094"
+ "shas": "557c25df0051a3b1cc5eef17e6b5672ec8cb2f05..ec42eab8be33fb30520e262289787add0c360792"
}
,{
"testCaseDescription": "ruby-subshell-delete-replacement-test",
@@ -266,7 +266,7 @@
"+`git status`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3614169030bf27a1ac6f8f23939e4fdd62e23094..33e028436fb47d3197a76f12be26f836bb2430ba"
+ "shas": "ec42eab8be33fb30520e262289787add0c360792..a8134eae4e792463e9bc682628731b8d9197b4cc"
}
,{
"testCaseDescription": "ruby-subshell-delete-test",
@@ -305,7 +305,7 @@
" `git status`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "33e028436fb47d3197a76f12be26f836bb2430ba..55764749f5eaa3048be7d288d183f336305acb28"
+ "shas": "a8134eae4e792463e9bc682628731b8d9197b4cc..3fb5c33c43b44640392f47239b35f1064d5a68f2"
}
,{
"testCaseDescription": "ruby-subshell-delete-rest-test",
@@ -343,5 +343,5 @@
"-`git status`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "55764749f5eaa3048be7d288d183f336305acb28..15350025c06bebe12d0443222898e58cfdc9bfad"
+ "shas": "3fb5c33c43b44640392f47239b35f1064d5a68f2..28aa7f167c9cd13555c78c78ce2484539360f682"
}]
diff --git a/test/corpus/diff-summaries/ruby/symbol.json b/test/corpus/diff-summaries/ruby/symbol.json
index 3999651ab..4d7f8f93a 100644
--- a/test/corpus/diff-summaries/ruby/symbol.json
+++ b/test/corpus/diff-summaries/ruby/symbol.json
@@ -66,7 +66,7 @@
"+:\"foo\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e1f12c295c3380e860cce36493b9639e688eb056..0abb28aad064adf6d0eba925738f77f14701e073"
+ "shas": "5063a6e97353e552c8a9a38f3cf69ef68790c3ab..e420b9e6d9f4c570e7ab4a005d6d445b311ead38"
}
,{
"testCaseDescription": "ruby-symbol-replacement-insert-test",
@@ -187,7 +187,7 @@
" :\"foo\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0abb28aad064adf6d0eba925738f77f14701e073..521afab3890beeaca5403ed4a601460ec3fd7b3d"
+ "shas": "e420b9e6d9f4c570e7ab4a005d6d445b311ead38..0fef26f562072aea7fb0f874d7552324daff2f4f"
}
,{
"testCaseDescription": "ruby-symbol-delete-insert-test",
@@ -299,7 +299,7 @@
" :\"foo\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "521afab3890beeaca5403ed4a601460ec3fd7b3d..3d942a410a7f7d55d9291817c9e3fd0bc35dd3d3"
+ "shas": "0fef26f562072aea7fb0f874d7552324daff2f4f..b6740a1b1e5dcaf4f5401b301bfd5a2b11638b67"
}
,{
"testCaseDescription": "ruby-symbol-replacement-test",
@@ -411,7 +411,7 @@
" :\"foo\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3d942a410a7f7d55d9291817c9e3fd0bc35dd3d3..03e015590af9acd4e45ab004a51eb64755c1c2d9"
+ "shas": "b6740a1b1e5dcaf4f5401b301bfd5a2b11638b67..82e24cd9a151e25fc034c9e58d5737ac2f306a21"
}
,{
"testCaseDescription": "ruby-symbol-delete-replacement-test",
@@ -580,7 +580,7 @@
"+:\"bar\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "03e015590af9acd4e45ab004a51eb64755c1c2d9..961da152c532f3f61b733523199957da8048f022"
+ "shas": "82e24cd9a151e25fc034c9e58d5737ac2f306a21..f29d1cd33117f62aa71f4b04b2c065e42c7e0a9f"
}
,{
"testCaseDescription": "ruby-symbol-delete-test",
@@ -653,7 +653,7 @@
" :\"bar\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "961da152c532f3f61b733523199957da8048f022..c90d41e01f717e24c60e7dee12c8f9c9c75e99ca"
+ "shas": "f29d1cd33117f62aa71f4b04b2c065e42c7e0a9f..7c8b899f33252e7a9207a2d200e41b48a1d6e823"
}
,{
"testCaseDescription": "ruby-symbol-delete-rest-test",
@@ -723,5 +723,5 @@
"-:\"bar\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c90d41e01f717e24c60e7dee12c8f9c9c75e99ca..c7a08a472303d6496e690e52bc239579bf99ef22"
+ "shas": "7c8b899f33252e7a9207a2d200e41b48a1d6e823..7882bb5b3e1cea5c33c4c86cf4a7935c534cf40c"
}]
diff --git a/test/corpus/diff-summaries/ruby/ternary.json b/test/corpus/diff-summaries/ruby/ternary.json
index bb9ef1b93..65992be25 100644
--- a/test/corpus/diff-summaries/ruby/ternary.json
+++ b/test/corpus/diff-summaries/ruby/ternary.json
@@ -34,7 +34,7 @@
"+foo ? case1 : case2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c68e6c55ea690a0be0abc87e1c88965206d29d27..6e4a963194d7b68bbdf9a61765b66818aed6ef2e"
+ "shas": "45978cfdd439c3dd5f0de02209a46608459cf93f..f7be7f1624b7f34d87e4e80c2fa3b414e7a92049"
}
,{
"testCaseDescription": "ruby-ternary-replacement-insert-test",
@@ -89,7 +89,7 @@
" foo ? case1 : case2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6e4a963194d7b68bbdf9a61765b66818aed6ef2e..e60a8912c6cb7084a84a6ca0630cba73ec65af8b"
+ "shas": "f7be7f1624b7f34d87e4e80c2fa3b414e7a92049..2ac4ccc1909af1cad778c9622ac3f6c3f940f92b"
}
,{
"testCaseDescription": "ruby-ternary-delete-insert-test",
@@ -196,7 +196,7 @@
" foo ? case1 : case2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e60a8912c6cb7084a84a6ca0630cba73ec65af8b..6aa75829daa6a0c9f0e0392a6048afedf29aaffd"
+ "shas": "2ac4ccc1909af1cad778c9622ac3f6c3f940f92b..4cac7094051efb27e4441ab80bba4b5a4a280ee3"
}
,{
"testCaseDescription": "ruby-ternary-replacement-test",
@@ -303,7 +303,7 @@
" foo ? case1 : case2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6aa75829daa6a0c9f0e0392a6048afedf29aaffd..694c6fe6f5e9c6d1639718fcd49c36d1a3ce6386"
+ "shas": "4cac7094051efb27e4441ab80bba4b5a4a280ee3..aa6d3a12975e64dac4e3c919f2dd4dcd45b244b8"
}
,{
"testCaseDescription": "ruby-ternary-delete-replacement-test",
@@ -374,7 +374,7 @@
"+bar ? a : b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "694c6fe6f5e9c6d1639718fcd49c36d1a3ce6386..f32d1a885a6a6a5dd4616eed802eaf900ec1205f"
+ "shas": "aa6d3a12975e64dac4e3c919f2dd4dcd45b244b8..d7db3226bb04614de36e2dba370fb457193cf6ae"
}
,{
"testCaseDescription": "ruby-ternary-delete-test",
@@ -413,7 +413,7 @@
" bar ? a : b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f32d1a885a6a6a5dd4616eed802eaf900ec1205f..d87aa24c7ed7370f947d29fac0cbc2834e0de06b"
+ "shas": "d7db3226bb04614de36e2dba370fb457193cf6ae..16e4a5414f2354a8ec2e442c78815b7ef4439e5e"
}
,{
"testCaseDescription": "ruby-ternary-delete-rest-test",
@@ -451,5 +451,5 @@
"-bar ? a : b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d87aa24c7ed7370f947d29fac0cbc2834e0de06b..745ee2cc606e7da317050022e6da3954b4cfbddd"
+ "shas": "16e4a5414f2354a8ec2e442c78815b7ef4439e5e..c9bdd0c09a302590952bf0f4b5303baa39e99888"
}]
diff --git a/test/corpus/diff-summaries/ruby/unless.json b/test/corpus/diff-summaries/ruby/unless.json
index fbcde343a..29b9cebd4 100644
--- a/test/corpus/diff-summaries/ruby/unless.json
+++ b/test/corpus/diff-summaries/ruby/unless.json
@@ -38,7 +38,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1ab25fb6630b041158518fa5f0e383c7cabbb087..7a5e6f012e554613b63af05795640d795d157619"
+ "shas": "3300daf6934aa86cb2ac7a51a11812902873e876..5e3c6c3a31f7fa51394d168c6de7dabcb4f638c5"
}
,{
"testCaseDescription": "ruby-unless-replacement-insert-test",
@@ -117,7 +117,7 @@
" else"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7a5e6f012e554613b63af05795640d795d157619..40a55e9fa2815c2bd3f2c16f751f6ca7a22751d4"
+ "shas": "5e3c6c3a31f7fa51394d168c6de7dabcb4f638c5..cfeb17463c9ea01f94a33099288bf0e26165bcd8"
}
,{
"testCaseDescription": "ruby-unless-delete-insert-test",
@@ -221,7 +221,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "40a55e9fa2815c2bd3f2c16f751f6ca7a22751d4..70310514687d08404de23e9ed25967a79e3c2734"
+ "shas": "cfeb17463c9ea01f94a33099288bf0e26165bcd8..6b7e44f260c02478c11600e2777de96d1b191c40"
}
,{
"testCaseDescription": "ruby-unless-replacement-test",
@@ -325,7 +325,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "70310514687d08404de23e9ed25967a79e3c2734..ee5f9df293b9c113dbab73e7b25f70802ccdc687"
+ "shas": "6b7e44f260c02478c11600e2777de96d1b191c40..49c3d24dd60b767873911ec8d241b3c917e1a23f"
}
,{
"testCaseDescription": "ruby-unless-delete-replacement-test",
@@ -379,7 +379,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ee5f9df293b9c113dbab73e7b25f70802ccdc687..6dc83e989b164e9f36d19ac661e951c264f00dc1"
+ "shas": "49c3d24dd60b767873911ec8d241b3c917e1a23f..e1b86a340f9fa327141d4be5d08e95b2f3629bac"
}
,{
"testCaseDescription": "ruby-unless-delete-test",
@@ -424,7 +424,7 @@
" unless y then"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6dc83e989b164e9f36d19ac661e951c264f00dc1..57fe27fb3ce3b603ca34c5b7cb177b31957110fb"
+ "shas": "e1b86a340f9fa327141d4be5d08e95b2f3629bac..e072310b768be2c745b0a5e6a508a4c0734748dd"
}
,{
"testCaseDescription": "ruby-unless-delete-rest-test",
@@ -480,5 +480,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "57fe27fb3ce3b603ca34c5b7cb177b31957110fb..0b7a3e0fb3d3a8a872b3fb94475d217170c8c393"
+ "shas": "e072310b768be2c745b0a5e6a508a4c0734748dd..d3c95751ff245559adc954a95a654ee6372e17d9"
}]
diff --git a/test/corpus/diff-summaries/ruby/until.json b/test/corpus/diff-summaries/ruby/until.json
index 58511b4a0..dfe8df131 100644
--- a/test/corpus/diff-summaries/ruby/until.json
+++ b/test/corpus/diff-summaries/ruby/until.json
@@ -51,7 +51,7 @@
"+foo until done"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7026d17ca4035741c0af3e0f18f07089112a285c..d902666374bcea504e3f0d55ccc679bbbce5bd73"
+ "shas": "851e5ccd21726e3d2aecc357f4b8e21ca48c8931..4303a90202c69065a37867ca51a4bfbeba285a32"
}
,{
"testCaseDescription": "ruby-until-replacement-insert-test",
@@ -127,7 +127,7 @@
" foo until done"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d902666374bcea504e3f0d55ccc679bbbce5bd73..32df363c541a7c77ab65b5bb75dee2b77844fd2d"
+ "shas": "4303a90202c69065a37867ca51a4bfbeba285a32..4d96f01ad37e757f0b9651bf629bdcff611fc2a3"
}
,{
"testCaseDescription": "ruby-until-delete-insert-test",
@@ -187,7 +187,7 @@
" foo until done"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "32df363c541a7c77ab65b5bb75dee2b77844fd2d..dcd9d8056c32892a61084923c308d995922b9dfe"
+ "shas": "4d96f01ad37e757f0b9651bf629bdcff611fc2a3..4e40107262b2628eb3cc5b0ed4e13fa640297983"
}
,{
"testCaseDescription": "ruby-until-replacement-test",
@@ -247,7 +247,7 @@
" foo until done"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "dcd9d8056c32892a61084923c308d995922b9dfe..a71be9027b5f431e4165cc0a4d2338d71f6c3cbb"
+ "shas": "4e40107262b2628eb3cc5b0ed4e13fa640297983..7e70dbf95d7435d3b9ced022e4f4f2a27d220650"
}
,{
"testCaseDescription": "ruby-until-delete-replacement-test",
@@ -340,7 +340,7 @@
"-foo until done"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a71be9027b5f431e4165cc0a4d2338d71f6c3cbb..9605efc6eac03e39c59b6f901fa1cde9998d7af1"
+ "shas": "7e70dbf95d7435d3b9ced022e4f4f2a27d220650..2e2ab60899ef6705435ca7a604800f51ec859951"
}
,{
"testCaseDescription": "ruby-until-delete-test",
@@ -398,7 +398,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9605efc6eac03e39c59b6f901fa1cde9998d7af1..174fdeba0540f656e3ae943c74a6229b4f4a040f"
+ "shas": "2e2ab60899ef6705435ca7a604800f51ec859951..e35cc063cfff537dd75f46eb23b9fb33a9696b73"
}
,{
"testCaseDescription": "ruby-until-delete-rest-test",
@@ -438,5 +438,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "174fdeba0540f656e3ae943c74a6229b4f4a040f..d77defc8ba86b790d4e36ddebce231ba3d7ca1ea"
+ "shas": "e35cc063cfff537dd75f46eb23b9fb33a9696b73..29a4ecc1f6a17f51d8dcbdb74ddaefc6e651d7ca"
}]
diff --git a/test/corpus/diff-summaries/ruby/when-else.json b/test/corpus/diff-summaries/ruby/when-else.json
index 09888f64f..3a1956ef8 100644
--- a/test/corpus/diff-summaries/ruby/when-else.json
+++ b/test/corpus/diff-summaries/ruby/when-else.json
@@ -37,7 +37,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c80a3d65f93f8306d95a0cdb9104f7ee5cce403d..e119b88b9002e2b8727e114b83b90a37ce4c349f"
+ "shas": "ab2392769172febef7b317850a4e30bb8ee02326..9cc96d5add1c5242be5da44a4567ee2f06ec8e02"
}
,{
"testCaseDescription": "ruby-when-else-insert-test",
@@ -79,7 +79,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e119b88b9002e2b8727e114b83b90a37ce4c349f..92bd6f3fd311d4bc5e25eefde9b86eeab6beed2c"
+ "shas": "9cc96d5add1c5242be5da44a4567ee2f06ec8e02..d56b1e0728e80c70b9d98f079f5845d418116deb"
}
,{
"testCaseDescription": "ruby-when-else-replacement-test",
@@ -133,7 +133,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "92bd6f3fd311d4bc5e25eefde9b86eeab6beed2c..b123cd02dbd014c1718a40056b80ea16fb376f80"
+ "shas": "d56b1e0728e80c70b9d98f079f5845d418116deb..3620c1d25d6dd0b4bff9c00b49b3bb6e815a913c"
}
,{
"testCaseDescription": "ruby-when-else-delete-replacement-test",
@@ -187,7 +187,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b123cd02dbd014c1718a40056b80ea16fb376f80..576339b2248a7896e3854c8c3cd8b6f35decef5d"
+ "shas": "3620c1d25d6dd0b4bff9c00b49b3bb6e815a913c..38b9c0e304b24a49fea228691d5efae98ee67f94"
}
,{
"testCaseDescription": "ruby-when-else-delete-insert-test",
@@ -229,7 +229,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "576339b2248a7896e3854c8c3cd8b6f35decef5d..adf495a082c50df48b0e69bf28747fccaf6b605c"
+ "shas": "38b9c0e304b24a49fea228691d5efae98ee67f94..5b0e767bd89ea3fe8975c480938f56124daa7518"
}
,{
"testCaseDescription": "ruby-when-else-teardown-test",
@@ -270,5 +270,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "adf495a082c50df48b0e69bf28747fccaf6b605c..585af1aa8a79718f22dd0fe0f8ac3051cfc56a4f"
+ "shas": "5b0e767bd89ea3fe8975c480938f56124daa7518..13b54918666502353431828fabfae483e79016f6"
}]
diff --git a/test/corpus/diff-summaries/ruby/when.json b/test/corpus/diff-summaries/ruby/when.json
index a0f1e3b39..c1ceb1e4d 100644
--- a/test/corpus/diff-summaries/ruby/when.json
+++ b/test/corpus/diff-summaries/ruby/when.json
@@ -35,7 +35,7 @@
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0f3ddff0899d7aea39733b5f21639fca68bd0b51..688d83e8dd2a73f66d21ccfce933e10c231db208"
+ "shas": "d7c0d9f3779b10092fd36936b786ecb673cc2cc8..17d779ef2c6c972d6d85d3b14a002d1745be325f"
}
,{
"testCaseDescription": "ruby-when-insert-test",
@@ -87,7 +87,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "688d83e8dd2a73f66d21ccfce933e10c231db208..4fc5f74c0f83584a712eb4c81b86a5e18bff4cd8"
+ "shas": "17d779ef2c6c972d6d85d3b14a002d1745be325f..9faadfa38973ac62c9d4c02737edffb50c212858"
}
,{
"testCaseDescription": "ruby-when-replacement-test",
@@ -128,7 +128,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4fc5f74c0f83584a712eb4c81b86a5e18bff4cd8..6597dc28377e7f366fabfc00a5ec9596e81022f0"
+ "shas": "9faadfa38973ac62c9d4c02737edffb50c212858..b2ba6648a26c6bcd7eaa19626f1215a2189632ab"
}
,{
"testCaseDescription": "ruby-when-delete-replacement-test",
@@ -169,7 +169,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6597dc28377e7f366fabfc00a5ec9596e81022f0..0adf2abade0a22431a3d9a4c80b35936108c716f"
+ "shas": "b2ba6648a26c6bcd7eaa19626f1215a2189632ab..de6d8774c6d563047bfbf1d2814b49a5f378123e"
}
,{
"testCaseDescription": "ruby-when-delete-insert-test",
@@ -221,7 +221,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0adf2abade0a22431a3d9a4c80b35936108c716f..d048b73ffb507bbc82b93b1519eb91a54d3ed65d"
+ "shas": "de6d8774c6d563047bfbf1d2814b49a5f378123e..ee477cb5e59568e80a3ad5c389a907f7216bd78f"
}
,{
"testCaseDescription": "ruby-when-teardown-test",
@@ -260,5 +260,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d048b73ffb507bbc82b93b1519eb91a54d3ed65d..c80a3d65f93f8306d95a0cdb9104f7ee5cce403d"
+ "shas": "ee477cb5e59568e80a3ad5c389a907f7216bd78f..ab2392769172febef7b317850a4e30bb8ee02326"
}]
diff --git a/test/corpus/diff-summaries/ruby/while.json b/test/corpus/diff-summaries/ruby/while.json
index 1e6e8e4e6..e9abeb5be 100644
--- a/test/corpus/diff-summaries/ruby/while.json
+++ b/test/corpus/diff-summaries/ruby/while.json
@@ -51,7 +51,7 @@
"+foo while run"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "eff0c95214265fb70e340d8da1ee09db4f4d7df9..1aa236d16bf593a4337e50a92272054d0186826a"
+ "shas": "4669d302b12c86884c870cd63d26b348abe19a22..9a7d8fdab7743c301b60cd7e85dc02e7270e7589"
}
,{
"testCaseDescription": "ruby-while-replacement-insert-test",
@@ -127,7 +127,7 @@
" foo while run"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1aa236d16bf593a4337e50a92272054d0186826a..e0ccbf6e413b2b896a576ee7e7abcb3023da6a58"
+ "shas": "9a7d8fdab7743c301b60cd7e85dc02e7270e7589..f9ba13bb8ab8a421d471d3913dc2a1c44e856416"
}
,{
"testCaseDescription": "ruby-while-delete-insert-test",
@@ -187,7 +187,7 @@
" foo while run"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e0ccbf6e413b2b896a576ee7e7abcb3023da6a58..1171716cdc84369a26a435f67dbd76b30c977186"
+ "shas": "f9ba13bb8ab8a421d471d3913dc2a1c44e856416..f8016e0decd91adf7570271f0375a8ad86660f49"
}
,{
"testCaseDescription": "ruby-while-replacement-test",
@@ -247,7 +247,7 @@
" foo while run"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1171716cdc84369a26a435f67dbd76b30c977186..fec4adce873d807bb5e17729c8b4778107fef41d"
+ "shas": "f8016e0decd91adf7570271f0375a8ad86660f49..df2784c0132f8b2212362731e4121c4d5d1cb517"
}
,{
"testCaseDescription": "ruby-while-delete-replacement-test",
@@ -340,7 +340,7 @@
"-foo while run"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fec4adce873d807bb5e17729c8b4778107fef41d..833695cd2c31cf20514dc359cb123327b2bed883"
+ "shas": "df2784c0132f8b2212362731e4121c4d5d1cb517..cc56102010bbcf45fc24ca7cd828db8a730ae24b"
}
,{
"testCaseDescription": "ruby-while-delete-test",
@@ -398,7 +398,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "833695cd2c31cf20514dc359cb123327b2bed883..ba132c4c0dde99cca3cce4fc5d7b22cc5d55b2b6"
+ "shas": "cc56102010bbcf45fc24ca7cd828db8a730ae24b..8a1a1e2860a01274c70ac7d1b90e86878c4f7ec7"
}
,{
"testCaseDescription": "ruby-while-delete-rest-test",
@@ -438,5 +438,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ba132c4c0dde99cca3cce4fc5d7b22cc5d55b2b6..7026d17ca4035741c0af3e0f18f07089112a285c"
+ "shas": "8a1a1e2860a01274c70ac7d1b90e86878c4f7ec7..851e5ccd21726e3d2aecc357f4b8e21ca48c8931"
}]
diff --git a/test/corpus/diff-summaries/ruby/yield.json b/test/corpus/diff-summaries/ruby/yield.json
index ac13590ac..8bc2de9bb 100644
--- a/test/corpus/diff-summaries/ruby/yield.json
+++ b/test/corpus/diff-summaries/ruby/yield.json
@@ -34,7 +34,7 @@
"+yield foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a60beed250baf3ff01e9f1d71d51d1eee16b3d18..3556774b6dc5c1a7533eceee366394528ecdf473"
+ "shas": "993b27aaf14a84e2d2f4f4d648b4c9c32e3b2378..b2c3e2db03921836dd66f6c4eef88d4aecef360a"
}
,{
"testCaseDescription": "ruby-yield-replacement-insert-test",
@@ -89,7 +89,7 @@
" yield foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3556774b6dc5c1a7533eceee366394528ecdf473..db88b503a8458bf2c6a3e237c00d22563a05b602"
+ "shas": "b2c3e2db03921836dd66f6c4eef88d4aecef360a..f927008d3c8f5635121036bef61f9e67f61f06ec"
}
,{
"testCaseDescription": "ruby-yield-delete-insert-test",
@@ -130,7 +130,7 @@
" yield foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "db88b503a8458bf2c6a3e237c00d22563a05b602..e41afc85a464e1cff658229120995f673b1a6b99"
+ "shas": "f927008d3c8f5635121036bef61f9e67f61f06ec..0dcdc89c436a694f2c74ec5ef3cc8549d0f1b4e7"
}
,{
"testCaseDescription": "ruby-yield-replacement-test",
@@ -171,7 +171,7 @@
" yield foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e41afc85a464e1cff658229120995f673b1a6b99..917be227b3772aa81cbb429c1f371351af2bdb1a"
+ "shas": "0dcdc89c436a694f2c74ec5ef3cc8549d0f1b4e7..79b8fb351ed575d4b80d712254e919f38d22c2e2"
}
,{
"testCaseDescription": "ruby-yield-delete-replacement-test",
@@ -242,7 +242,7 @@
"+yield"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "917be227b3772aa81cbb429c1f371351af2bdb1a..3b157e8f1b36071ba23fb1c2823e4852c2afe775"
+ "shas": "79b8fb351ed575d4b80d712254e919f38d22c2e2..a5df4b0c023249752f080c000166c57d8e7ae4c5"
}
,{
"testCaseDescription": "ruby-yield-delete-test",
@@ -281,7 +281,7 @@
" yield"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3b157e8f1b36071ba23fb1c2823e4852c2afe775..42b45e4916eac44a57f89712d87393f8c52c282d"
+ "shas": "a5df4b0c023249752f080c000166c57d8e7ae4c5..66d929181e1306e0ef760ae28f582d37cd0d132a"
}
,{
"testCaseDescription": "ruby-yield-delete-rest-test",
@@ -319,5 +319,5 @@
"-yield"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "42b45e4916eac44a57f89712d87393f8c52c282d..eff0c95214265fb70e340d8da1ee09db4f4d7df9"
+ "shas": "66d929181e1306e0ef760ae28f582d37cd0d132a..4669d302b12c86884c870cd63d26b348abe19a22"
}]
diff --git a/test/corpus/repos/go b/test/corpus/repos/go
index 13e9de620..b704517ca 160000
--- a/test/corpus/repos/go
+++ b/test/corpus/repos/go
@@ -1 +1 @@
-Subproject commit 13e9de620f0e981a263aa8306692c8e3b7bae8a9
+Subproject commit b704517caf7ad227154e0582b74255cd4065e091
diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript
index 80946fe66..abce7caf7 160000
--- a/test/corpus/repos/javascript
+++ b/test/corpus/repos/javascript
@@ -1 +1 @@
-Subproject commit 80946fe6667b3843c0bd704136ac929ca5f2e3e0
+Subproject commit abce7caf7e67e197076f10ee997f4a8e08480f93
diff --git a/test/corpus/repos/ruby b/test/corpus/repos/ruby
index 97513ccc9..d873b65ce 160000
--- a/test/corpus/repos/ruby
+++ b/test/corpus/repos/ruby
@@ -1 +1 @@
-Subproject commit 97513ccc92beee8dc279d44117dce9155e578efe
+Subproject commit d873b65ce39ee8f41bdbdb381d42fa08d4d6828b
diff --git a/test/diffs/asymmetrical-context.split.js b/test/diffs/asymmetrical-context.split.js
index d389f8f30..4bdc27d55 100644
--- a/test/diffs/asymmetrical-context.split.js
+++ b/test/diffs/asymmetrical-context.split.js
@@ -1,7 +1,7 @@
-
1
+1
-1
@@ -20,9 +20,9 @@
5
-2 2
-6 3
diff --git a/test/diffs/insert.split.js b/test/diffs/insert.split.js
index c6866bc2f..4b247c35f 100644
--- a/test/diffs/insert.split.js
+++ b/test/diffs/insert.split.js
@@ -1,11 +1,11 @@
-1
+1
-1
-2 2
diff --git a/test/diffs/multiline-insert.split.js b/test/diffs/multiline-insert.split.js
index aa9565869..d3e951207 100644
--- a/test/diffs/multiline-insert.split.js
+++ b/test/diffs/multiline-insert.split.js
@@ -1,7 +1,7 @@
-1
+1
-1
@@ -9,16 +9,16 @@
-3
4
-2 2
-5 3
diff --git a/test/diffs/nested-insert.split.js b/test/diffs/nested-insert.split.js
index 66acbb19e..98fffccd4 100644
--- a/test/diffs/nested-insert.split.js
+++ b/test/diffs/nested-insert.split.js
@@ -4,13 +4,13 @@
1
-2 2
-2
-3 3
diff --git a/test/diffs/newline-at-eof.json.js b/test/diffs/newline-at-eof.json.js
index 8e1174f59..aa7265b10 100644
--- a/test/diffs/newline-at-eof.json.js
+++ b/test/diffs/newline-at-eof.json.js
@@ -1 +1 @@
-{"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/newline-at-eof.A.js","test/diffs/newline-at-eof.B.js"],"rows":[[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,29]}],"hasChanges":false,"range":[0,29],"number":1},{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,29]}],"hasChanges":false,"range":[0,29],"number":1}],[{"terms":[{"category":"Program","children":[],"range":[29,29]}],"hasChanges":false,"range":[29,29],"number":2},{"terms":[{"category":"Program","children":[],"range":[29,30]}],"hasChanges":false,"range":[29,30],"number":2}],[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[30,37]},{"category":"Identifier","range":[38,41]},{"category":"StringLiteral","range":[42,53]}],"range":[30,54]}],"patch":"insert","range":[30,55]}],"range":[30,56]}],"hasChanges":true,"range":[30,56],"number":3}],[{"terms":[{"category":"Program","children":[],"range":[56,56]}],"hasChanges":false,"range":[56,56],"number":4}]]}
\ No newline at end of file
+{"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/newline-at-eof.A.js","test/diffs/newline-at-eof.B.js"],"rows":[[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"FunctionCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,29]}],"hasChanges":false,"range":[0,29],"number":1},{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"FunctionCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,29]}],"hasChanges":false,"range":[0,29],"number":1}],[{"terms":[{"category":"Program","children":[],"range":[29,29]}],"hasChanges":false,"range":[29,29],"number":2},{"terms":[{"category":"Program","children":[],"range":[29,30]}],"hasChanges":false,"range":[29,30],"number":2}],[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"FunctionCall","children":[{"category":"Identifier","range":[30,37]},{"category":"Identifier","range":[38,41]},{"category":"StringLiteral","range":[42,53]}],"range":[30,54]}],"patch":"insert","range":[30,55]}],"range":[30,56]}],"hasChanges":true,"range":[30,56],"number":3}],[{"terms":[{"category":"Program","children":[],"range":[56,56]}],"hasChanges":false,"range":[56,56],"number":4}]]}
\ No newline at end of file
diff --git a/test/diffs/newline-at-eof.split.js b/test/diffs/newline-at-eof.split.js
index 432c466f7..8415e6b28 100644
--- a/test/diffs/newline-at-eof.split.js
+++ b/test/diffs/newline-at-eof.split.js
@@ -1,7 +1,7 @@
-1 console .log ("hello, world" ) ;
+1 console .log ("hello, world" ) ;
-1 console .log ("hello, world" ) ;
+1 console .log ("hello, world" ) ;
2
@@ -9,7 +9,7 @@
-3
diff --git a/test/diffs/no-newline-at-eof.json.js b/test/diffs/no-newline-at-eof.json.js
index 544b3796d..f2344694e 100644
--- a/test/diffs/no-newline-at-eof.json.js
+++ b/test/diffs/no-newline-at-eof.json.js
@@ -1 +1 @@
-{"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/no-newline-at-eof.A.js","test/diffs/no-newline-at-eof.B.js"],"rows":[[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,28]}],"hasChanges":false,"range":[0,28],"number":1},{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,29]}],"hasChanges":false,"range":[0,29],"number":1}],[{"terms":[{"category":"Program","children":[],"range":[29,30]}],"hasChanges":false,"range":[29,30],"number":2}],[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[30,37]},{"category":"Identifier","range":[38,41]},{"category":"StringLiteral","range":[42,53]}],"range":[30,54]}],"patch":"insert","range":[30,55]}],"range":[30,55]}],"hasChanges":true,"range":[30,55],"number":3}]]}
\ No newline at end of file
+{"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/no-newline-at-eof.A.js","test/diffs/no-newline-at-eof.B.js"],"rows":[[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"FunctionCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,28]}],"hasChanges":false,"range":[0,28],"number":1},{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"FunctionCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,29]}],"hasChanges":false,"range":[0,29],"number":1}],[{"terms":[{"category":"Program","children":[],"range":[29,30]}],"hasChanges":false,"range":[29,30],"number":2}],[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"FunctionCall","children":[{"category":"Identifier","range":[30,37]},{"category":"Identifier","range":[38,41]},{"category":"StringLiteral","range":[42,53]}],"range":[30,54]}],"patch":"insert","range":[30,55]}],"range":[30,55]}],"hasChanges":true,"range":[30,55],"number":3}]]}
\ No newline at end of file
diff --git a/test/diffs/no-newline-at-eof.split.js b/test/diffs/no-newline-at-eof.split.js
index f877070d3..1e0778e6a 100644
--- a/test/diffs/no-newline-at-eof.split.js
+++ b/test/diffs/no-newline-at-eof.split.js
@@ -1,6 +1,6 @@
-1 console .log ("hello, world" ) ;
-1 console .log ("hello, world" ) ;
+1 console .log ("hello, world" ) ;
+1 console .log ("hello, world" ) ;
@@ -8,6 +8,6 @@
-3
+3
\ No newline at end of file