diff --git a/src/Category.hs b/src/Category.hs
index f7cca715f..a63f9a544 100644
--- a/src/Category.hs
+++ b/src/Category.hs
@@ -126,6 +126,15 @@ data Category
| Until
-- | A unless/else expression.
| Unless
+ | Begin
+ | Else
+ | Elsif
+ | Ensure
+ | Rescue
+ | RescueModifier
+ | When
+ | RescuedException
+ | Negate
deriving (Eq, Generic, Ord, Show)
-- Instances
@@ -186,6 +195,15 @@ instance Arbitrary Category where
, pure Yield
, pure Until
, pure Unless
+ , pure Begin
+ , pure Else
+ , pure Elsif
+ , pure Ensure
+ , pure Rescue
+ , pure RescueModifier
+ , pure When
+ , pure RescuedException
+ , pure Negate
, Other <$> arbitrary
]
diff --git a/src/DiffSummary.hs b/src/DiffSummary.hs
index 224eb39e3..c14fd613e 100644
--- a/src/DiffSummary.hs
+++ b/src/DiffSummary.hs
@@ -47,12 +47,19 @@ identifiable term = isIdentifiable (unwrap term) term
S.MathAssignment{} -> Identifiable
S.VarAssignment{} -> Identifiable
S.SubscriptAccess{} -> Identifiable
+ S.Module{} -> Identifiable
S.Class{} -> Identifiable
S.Method{} -> Identifiable
S.Leaf{} -> Identifiable
S.DoWhile{} -> Identifiable
S.Import{} -> Identifiable
S.Export{} -> Identifiable
+ S.Ternary{} -> Identifiable
+ S.If{} -> Identifiable
+ S.Try{} -> Identifiable
+ S.Switch{} -> Identifiable
+ S.Case{} -> Identifiable
+ S.Rescue{} -> Identifiable
_ -> Unidentifiable
data JSONSummary summary span = JSONSummary { summary :: summary, span :: span }
@@ -139,6 +146,10 @@ determiner :: DiffInfo -> Doc
determiner (LeafInfo "number" _ _) = ""
determiner (LeafInfo "integer" _ _) = ""
determiner (LeafInfo "boolean" _ _) = ""
+determiner (LeafInfo "begin statement" _ _) = "a"
+determiner (LeafInfo "else block" _ _) = "an"
+determiner (LeafInfo "ensure block" _ _) = "an"
+determiner (LeafInfo "when block" _ _) = "a"
determiner (LeafInfo "anonymous function" _ _) = "an"
determiner (BranchInfo bs _ _) = determiner (last bs)
determiner _ = "the"
@@ -152,6 +163,10 @@ toLeafInfos leaf = pure . flip JSONSummary (sourceSpan leaf) $ case leaf of
(LeafInfo "integer" termName _) -> squotes $ toDoc termName
(LeafInfo "boolean" termName _) -> squotes $ toDoc termName
(LeafInfo "anonymous function" termName _) -> toDoc termName <+> "function"
+ (LeafInfo cName@"begin statement" _ _) -> toDoc cName
+ (LeafInfo cName@"else block" _ _) -> toDoc cName
+ (LeafInfo cName@"ensure block" _ _) -> toDoc cName
+ (LeafInfo cName@"when block" _ _) -> toDoc cName
(LeafInfo cName@"string" termName _) -> toDoc termName <+> toDoc cName
(LeafInfo cName@"export statement" termName _) -> toDoc termName <+> toDoc cName
(LeafInfo cName@"import statement" termName _) -> toDoc termName <+> toDoc cName
@@ -192,12 +207,9 @@ toTermName source term = case unwrap term of
(_, _) -> toTermName' base <> "[" <> toTermName' element <> "]"
S.VarAssignment varId _ -> toTermName' varId
S.VarDecl decl -> toTermName' decl
- -- TODO: We should remove Args from Syntax since I don't think we should ever
- -- evaluate Args as a single toTermName Text - joshvera
- S.Args args -> mconcat $ toTermName' <$> args
-- TODO: We should remove Case from Syntax since I don't think we should ever
-- evaluate Case as a single toTermName Text - joshvera
- S.Case expr _ -> toTermName' expr
+ S.Case expr _ -> termNameFromSource expr
S.Switch expr _ -> toTermName' expr
S.Ternary expr _ -> toTermName' expr
S.MathAssignment id _ -> toTermName' id
@@ -213,10 +225,10 @@ toTermName source term = case unwrap term of
S.DoWhile _ expr -> toTermName' expr
S.Throw expr -> termNameFromSource expr
S.Constructor expr -> toTermName' expr
- S.Try expr _ _ -> termNameFromSource expr
+ S.Try clauses _ _ _ -> termNameFromChildren term clauses
S.Array _ -> termNameFromSource term
S.Class identifier _ _ -> toTermName' identifier
- S.Method identifier _ _ -> toTermName' identifier
+ S.Method identifier args _ -> toTermName' identifier <> paramsToArgNames args
S.Comment a -> toCategoryName a
S.Commented _ _ -> termNameFromChildren term (toList $ unwrap term)
S.Module identifier _ -> toTermName' identifier
@@ -226,8 +238,8 @@ toTermName source term = case unwrap term of
S.Export (Just identifier) [] -> "{ " <> toTermName' identifier <> " }"
S.Export (Just identifier) expr -> "{ " <> intercalate ", " (termNameFromSource <$> expr) <> " }" <> " from " <> toTermName' identifier
S.ConditionalAssignment id _ -> toTermName' id
- S.Until expr _ -> toTermName' expr
- S.Unless expr _ -> termNameFromSource expr
+ S.Negate expr -> toTermName' expr
+ S.Rescue args _ -> intercalate ", " $ toTermName' <$> args
where toTermName' = toTermName source
termNameFromChildren term children = termNameFromRange (unionRangesFrom (range term) (range <$> children))
termNameFromSource term = termNameFromRange (range term)
@@ -244,6 +256,20 @@ parentContexts contexts = hsep $ either identifiableDoc annotatableDoc <$> conte
where
identifiableDoc (c, t) = case c of
C.Assignment -> "in an" <+> catName c <+> "to" <+> termName t
+ C.Begin -> "in a" <+> catName c
+ C.Else -> "in an" <+> catName c
+ C.Elsif -> "in the" <+> squotes (termName t) <+> catName c
+ C.Method -> "in the" <+> squotes (termName t) <+> catName c
+ C.Ternary -> "in the" <+> squotes (termName t) <+> catName c
+ C.Ensure -> "in an" <+> catName c
+ C.Rescue -> case t of
+ "" -> "in a" <+> catName c
+ _ -> "in the" <+> squotes (termName t) <+> catName c
+ C.RescueModifier -> "in the" <+> squotes ("rescue" <+> termName t) <+> "modifier"
+ C.If -> "in the" <+> squotes (termName t) <+> catName c
+ C.Case -> "in the" <+> squotes (termName t) <+> catName c
+ C.Switch -> "in the" <+> squotes (termName t) <+> catName c
+ C.When -> "in a" <+> catName c
_ -> "in the" <+> termName t <+> catName c
annotatableDoc (c, t) = "of the" <+> squotes (termName t) <+> catName c
catName = toDoc . toCategoryName
@@ -324,7 +350,7 @@ instance HasCategory Category where
NumberLiteral -> "number"
Other s -> s
C.Pair -> "pair"
- Params -> "params"
+ C.Params -> "params"
Program -> "top level"
Regex -> "regex"
StringLiteral -> "string"
@@ -354,6 +380,15 @@ instance HasCategory Category where
C.Yield -> "yield statement"
C.Until -> "until statement"
C.Unless -> "unless statement"
+ C.Begin -> "begin statement"
+ C.Else -> "else block"
+ C.Elsif -> "elsif block"
+ C.Ensure -> "ensure block"
+ C.Rescue -> "rescue block"
+ C.RescueModifier -> "rescue modifier"
+ C.When -> "when comparison"
+ C.RescuedException -> "last exception"
+ C.Negate -> "negate"
instance HasField fields Category => HasCategory (SyntaxTerm leaf fields) where
toCategoryName = toCategoryName . category . extract
diff --git a/src/Language/JavaScript.hs b/src/Language/JavaScript.hs
index 8122d11c0..e036d2162 100644
--- a/src/Language/JavaScript.hs
+++ b/src/Language/JavaScript.hs
@@ -41,21 +41,20 @@ termConstructor source sourceSpan name range children
S.Indexed rest -> S.Indexed $ a : rest
_ -> S.Indexed children
("comma_op", _ ) -> S.Error children
- ("function_call", _) -> case runCofree <$> children of
- [ _ :< S.MemberAccess{..}, _ :< S.Args args ] -> S.MethodCall memberId property args
- [ _ :< S.MemberAccess{..} ] -> S.MethodCall memberId property []
- [ function, _ :< S.Args args ] -> S.FunctionCall (cofree function) args
- (x:xs) -> S.FunctionCall (cofree x) (cofree <$> xs)
+ ("function_call", _) -> case children of
+ member : args | category (extract member) == MemberAccess -> case toList (unwrap member) of
+ [target, method] -> S.MethodCall target method (toList . unwrap =<< args)
+ _ -> S.Error children
+ function : args -> S.FunctionCall function (toList . unwrap =<< args)
_ -> S.Error children
("ternary", condition : cases) -> S.Ternary condition cases
("ternary", _ ) -> S.Error children
- ("arguments", _) -> S.Args children
("var_assignment", [ x, y ]) -> S.VarAssignment x y
("var_assignment", _ ) -> S.Error children
("var_declaration", _) -> S.Indexed $ toVarDecl <$> children
("switch_statement", expr : rest) -> S.Switch expr rest
("switch_statement", _ ) -> S.Error children
- ("case", [ expr, body ]) -> S.Case expr body
+ ("case", [ expr, body ]) -> S.Case expr [body]
("case", _ ) -> S.Error children
("object", _) -> S.Object $ foldMap toTuple children
("pair", _) -> S.Fixed children
@@ -70,13 +69,14 @@ termConstructor source sourceSpan name range children
("throw_statment", _ ) -> S.Error children
("new_expression", [ expr ]) -> S.Constructor expr
("new_expression", _ ) -> S.Error children
- ("try_statement", [ body ]) -> S.Try body Nothing Nothing
- ("try_statement", [ body, catch ]) | Catch <- category (extract catch) -> S.Try body (Just catch) Nothing
- ("try_statement", [ body, finally ]) | Finally <- category (extract finally) -> S.Try body Nothing (Just finally)
- ("try_statement", [ body, catch, finally ])
- | Catch <- category (extract catch)
- , Finally <- category (extract finally) -> S.Try body (Just catch) (Just finally)
- ("try_statement", _ ) -> S.Error children
+ ("try_statement", _) -> case children of
+ [ body ] -> S.Try [body] [] Nothing Nothing
+ [ body, catch ] | Catch <- category (extract catch) -> S.Try [body] [catch] Nothing Nothing
+ [ body, finally ] | Finally <- category (extract finally) -> S.Try [body] [] Nothing (Just finally)
+ [ body, catch, finally ]
+ | Catch <- category (extract catch)
+ , Finally <- category (extract finally) -> S.Try [body] [catch] Nothing (Just finally)
+ _ -> S.Error children
("array", _) -> S.Array children
("method_definition", [ identifier, params, exprs ]) -> S.Method identifier (toList (unwrap params)) (toList (unwrap exprs))
("method_definition", [ identifier, exprs ]) -> S.Method identifier [] (toList (unwrap exprs))
diff --git a/src/Language/Ruby.hs b/src/Language/Ruby.hs
index 9f4e2c123..ffab7f311 100644
--- a/src/Language/Ruby.hs
+++ b/src/Language/Ruby.hs
@@ -2,6 +2,7 @@
module Language.Ruby where
import Data.Record
+import Data.List (partition)
import Info
import Prologue
import Source
@@ -10,7 +11,7 @@ import qualified Syntax as S
import Term
operators :: [Text]
-operators = ["and", "boolean_and", "or", "boolean_or", "bitwise_or", "bitwise_and", "shift", "relational", "comparison"]
+operators = [ "and", "boolean_and", "or", "boolean_or", "bitwise_or", "bitwise_and", "shift", "relational", "comparison" ]
functions :: [Text]
functions = [ "lambda_literal", "lambda_expression" ]
@@ -24,59 +25,96 @@ termConstructor
-> IO (Term (S.Syntax Text) (Record '[Range, Category, SourceSpan])) -- ^ The resulting term, in IO.
termConstructor source sourceSpan name range children
| name == "ERROR" = withDefaultInfo (S.Error children)
+ | name == "unless_modifier" = case children of
+ [ lhs, rhs ] -> do
+ condition <- withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)
+ withDefaultInfo $ S.If condition [lhs]
+ _ -> withDefaultInfo $ S.Error children
+ | name == "unless_statement" = case children of
+ ( expr : rest ) -> do
+ condition <- withRecord (setCategory (extract expr) Negate) (S.Negate expr)
+ withDefaultInfo $ S.If condition rest
+ _ -> withDefaultInfo $ S.Error children
+ | name == "until_modifier" = case children of
+ [ lhs, rhs ] -> do
+ condition <- withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)
+ withDefaultInfo $ S.While condition [lhs]
+ _ -> withDefaultInfo $ S.Error children
+ | name == "until_statement" = case children of
+ ( expr : rest ) -> do
+ condition <- withRecord (setCategory (extract expr) Negate) (S.Negate expr)
+ withDefaultInfo $ S.While condition rest
+ _ -> withDefaultInfo $ S.Error children
| otherwise = withDefaultInfo $ case (name, children) of
- ("argument_list", _) -> S.Args children
- ("array", _) -> S.Array children
+ ("array", _ ) -> S.Array children
("assignment", [ identifier, value ]) -> S.Assignment identifier value
("assignment", _ ) -> S.Error children
- ("case_statement", expr : rest) -> S.Switch expr rest
+ ("begin_statement", _ ) -> case partition (\x -> category (extract x) == Rescue) children of
+ (rescues, rest) -> case partition (\x -> category (extract x) == Ensure || category (extract x) == Else) rest of
+ (ensureElse, body) -> case ensureElse of
+ [ elseBlock, ensure ]
+ | Else <- category (extract elseBlock)
+ , Ensure <- category (extract ensure) -> S.Try body rescues (Just elseBlock) (Just ensure)
+ [ ensure, elseBlock ]
+ | Ensure <- category (extract ensure)
+ , Else <- category (extract elseBlock) -> S.Try body rescues (Just elseBlock) (Just ensure)
+ [ elseBlock ] | Else <- category (extract elseBlock) -> S.Try body rescues (Just elseBlock) Nothing
+ [ ensure ] | Ensure <- category (extract ensure) -> S.Try body rescues Nothing (Just ensure)
+ _ -> S.Try body rescues Nothing Nothing
+ ("case_statement", expr : body ) -> S.Switch expr body
("case_statement", _ ) -> S.Error children
+ ("when_block", condition : body ) -> S.Case condition body
+ ("when_block", _ ) -> S.Error children
("class_declaration", [ identifier, superclass, definitions ]) -> S.Class identifier (Just superclass) (toList (unwrap definitions))
("class_declaration", [ identifier, definitions ]) -> S.Class identifier Nothing (toList (unwrap definitions))
("class_declaration", _ ) -> S.Error children
- ("comment", _) -> S.Comment . toText $ slice range source
+ ("comment", _ ) -> S.Comment . toText $ slice range source
("conditional_assignment", [ identifier, value ]) -> S.ConditionalAssignment identifier value
("conditional_assignment", _ ) -> S.Error children
("conditional", condition : cases) -> S.Ternary condition cases
("conditional", _ ) -> S.Error children
- ("function_call", _) -> case runCofree <$> children of
- [ _ :< S.MemberAccess{..}, _ :< S.Args args ] -> S.MethodCall memberId property args
- [ _ :< S.MemberAccess{..} ] -> S.MethodCall memberId property []
- [ function, _ :< S.Args args ] -> S.FunctionCall (cofree function) args
- (x:xs) -> S.FunctionCall (cofree x) (cofree <$> xs)
+ ("function_call", _ ) -> case children of
+ member : args | category (extract member) == MemberAccess -> case toList (unwrap member) of
+ [target, method] -> S.MethodCall target method (toList . unwrap =<< args)
+ _ -> S.Error children
+ function : args -> S.FunctionCall function (toList . unwrap =<< args)
_ -> S.Error children
- ("hash", _) -> S.Object $ foldMap toTuple children
+ ("hash", _ ) -> S.Object $ foldMap toTuple children
("if_modifier", [ lhs, condition ]) -> S.If condition [lhs]
("if_modifier", _ ) -> S.Error children
- ("if_statement", expr : rest ) -> S.If expr rest
+ ("if_statement", condition : body ) -> S.If condition body
("if_statement", _ ) -> S.Error children
+ ("elsif_block", condition : body ) -> S.If condition body
+ ("elsif_block", _ ) -> S.Error children
("element_reference", [ base, element ]) -> S.SubscriptAccess base element
("element_reference", _ ) -> S.Error children
+ ("for_statement", lhs : expr : rest ) -> S.For [lhs, expr] rest
+ ("for_statement", _ ) -> S.Error children
("math_assignment", [ identifier, value ]) -> S.MathAssignment identifier value
("math_assignment", _ ) -> S.Error children
("member_access", [ base, property ]) -> S.MemberAccess base property
("member_access", _ ) -> S.Error children
- ("method_declaration", [ identifier, params, exprs ]) -> S.Method identifier (toList (unwrap params)) (toList (unwrap exprs))
- ("method_declaration", [ identifier, exprs ]) -> S.Method identifier [] (toList (unwrap exprs))
- ("method_declaration", _ ) -> S.Error children
+ ("method_declaration", _ ) -> case children of
+ identifier : params : body | Params <- category (extract params) -> S.Method identifier (toList (unwrap params)) body
+ identifier : body -> S.Method identifier [] body
+ _ -> S.Error children
("module_declaration", identifier : body ) -> S.Module identifier body
("module_declaration", _ ) -> S.Error children
+ ("rescue_block", _ ) -> case children of
+ args : lastException : rest
+ | Args <- category (extract args)
+ , RescuedException <- category (extract lastException) -> S.Rescue (toList (unwrap args) <> [lastException]) rest
+ lastException : rest | RescuedException <- category (extract lastException) -> S.Rescue [lastException] rest
+ args : body | Args <- category (extract args) -> S.Rescue (toList (unwrap args)) body
+ body -> S.Rescue [] body
+ ("rescue_modifier", [lhs, rhs] ) -> S.Rescue [lhs] [rhs]
+ ("rescue_modifier", _ ) -> S.Error children
("return_statement", _ ) -> S.Return (listToMaybe children)
- ("unless_modifier", [ lhs, condition ]) -> S.Unless condition [lhs]
- ("unless_modifier", _ ) -> S.Error children
- ("unless_statement", expr : rest ) -> S.Unless expr rest
- ("unless_statement", _ ) -> S.Error children
- ("until_modifier", [ lhs, condition ]) -> S.Until condition [lhs]
- ("until_modifier", _ ) -> S.Error children
- ("until_statement", expr : rest ) -> S.Until expr rest
- ("until_statement", _ ) -> S.Error children
("while_modifier", [ lhs, condition ]) -> S.While condition [lhs]
("while_modifier", _ ) -> S.Error children
("while_statement", expr : rest ) -> S.While expr rest
("while_statement", _ ) -> S.Error children
- ("yield", _) -> S.Yield (listToMaybe children)
- ("for_statement", lhs : expr : rest ) -> S.For [lhs, expr] rest
- ("for_statement", _ ) -> S.Error children
+ ("yield", _ ) -> S.Yield (listToMaybe children)
_ | name `elem` operators -> S.Operator children
_ | name `elem` functions -> case children of
[ body ] -> S.AnonymousFunction [] [body]
@@ -85,9 +123,13 @@ termConstructor source sourceSpan name range children
(_, []) -> S.Leaf . toText $ slice range source
_ -> S.Indexed children
where
- withDefaultInfo syntax = do
+ withRecord record syntax = pure $! cofree (record :< syntax)
+ withCategory category syntax = do
sourceSpan' <- sourceSpan
- pure $! cofree ((range .: categoryForRubyName name .: sourceSpan' .: RNil) :< syntax)
+ pure $! cofree ((range .: category .: sourceSpan' .: RNil) :< syntax)
+ withDefaultInfo syntax = case syntax of
+ S.MethodCall{} -> withCategory MethodCall syntax
+ _ -> withCategory (categoryForRubyName name) syntax
categoryForRubyName :: Text -> Category
categoryForRubyName = \case
@@ -95,22 +137,22 @@ categoryForRubyName = \case
"argument_list" -> Args
"array" -> ArrayLiteral
"assignment" -> Assignment
- "begin_statement" -> ExpressionStatements
+ "begin_statement" -> Begin
"bitwise_and" -> BitwiseOperator -- bitwise and, e.g &.
"bitwise_or" -> BitwiseOperator -- bitwise or, e.g. ^, |.
"boolean_and" -> BooleanOperator -- boolean and, e.g. &&.
"boolean_or" -> BooleanOperator -- boolean or, e.g. &&.
"boolean" -> Boolean
- "case_statement" -> Switch
+ "case_statement" -> Case
"class_declaration" -> Class
"comment" -> Comment
"comparison" -> RelationalOperator -- comparison operator, e.g. <, <=, >=, >.
"conditional_assignment" -> ConditionalAssignment
"conditional" -> Ternary
"element_reference" -> SubscriptAccess
- "else_block" -> ExpressionStatements
- "elsif_block" -> ExpressionStatements
- "ensure_block" -> ExpressionStatements
+ "else_block" -> Else
+ "elsif_block" -> Elsif
+ "ensure_block" -> Ensure
"ERROR" -> Error
"float" -> NumberLiteral
"for_statement" -> For
@@ -123,6 +165,7 @@ categoryForRubyName = \case
"if_statement" -> If
"integer" -> IntegerLiteral
"interpolation" -> Interpolation
+ "rescued_exception" -> RescuedException
"math_assignment" -> MathAssignment
"member_access" -> MemberAccess
"method_declaration" -> Method
@@ -132,18 +175,18 @@ categoryForRubyName = \case
"program" -> Program
"regex" -> Regex
"relational" -> RelationalOperator -- relational operator, e.g. ==, !=, ===, <=>, =~, !~.
- "rescue_block" -> ExpressionStatements
+ "rescue_block" -> Rescue
+ "rescue_modifier" -> RescueModifier
"return_statement" -> Return
"shift" -> BitwiseOperator -- bitwise shift, e.g <<, >>.
"string" -> StringLiteral
"subshell" -> Subshell
"symbol" -> SymbolLiteral
- "then_block" -> ExpressionStatements
"unless_modifier" -> Unless
"unless_statement" -> Unless
"until_modifier" -> Until
"until_statement" -> Until
- "when_block" -> ExpressionStatements
+ "when_block" -> When
"while_modifier" -> While
"while_statement" -> While
"yield" -> Yield
diff --git a/src/Renderer/JSON.hs b/src/Renderer/JSON.hs
index 4d8f34e27..c3178fc49 100644
--- a/src/Renderer/JSON.hs
+++ b/src/Renderer/JSON.hs
@@ -100,7 +100,6 @@ syntaxToTermField syntax = case syntax of
S.MathAssignment identifier value -> [ "identifier" .= identifier ] <> [ "value" .= value ]
S.MemberAccess identifier value -> [ "identifier" .= identifier ] <> [ "value" .= value ]
S.MethodCall identifier methodIdentifier parameters -> [ "identifier" .= identifier ] <> [ "methodIdentifier" .= methodIdentifier ] <> [ "parameters" .= parameters ]
- S.Args c -> childrenFields c
S.Operator syntaxes -> [ "operatorSyntaxes" .= syntaxes ]
S.VarDecl declaration -> [ "declaration" .= declaration ]
S.VarAssignment identifier value -> [ "identifier" .= identifier ] <> [ "value" .= value ]
@@ -118,7 +117,7 @@ syntaxToTermField syntax = case syntax of
S.Return expression -> [ "expression" .= expression ]
S.Throw c -> [ "expression" .= c ]
S.Constructor expression -> [ "expression" .= expression ]
- S.Try body catchExpression finallyExpression -> [ "body" .= body ] <> [ "catchExpression" .= catchExpression ] <> [ "finallyExpression" .= finallyExpression ]
+ S.Try body catchExpression elseExpression finallyExpression -> [ "body" .= body ] <> [ "catchExpression" .= catchExpression ] <> [ "elseExpression" .= elseExpression ] <> [ "finallyExpression" .= finallyExpression ]
S.Array c -> childrenFields c
S.Class identifier superclass definitions -> [ "identifier" .= identifier ] <> [ "superclass" .= superclass ] <> [ "definitions" .= definitions ]
S.Method identifier parameters definitions -> [ "identifier" .= identifier ] <> [ "parameters" .= parameters ] <> [ "definitions" .= definitions ]
@@ -128,6 +127,6 @@ syntaxToTermField syntax = case syntax of
S.Export identifier statements -> [ "identifier" .= identifier ] <> [ "statements" .= statements ]
S.ConditionalAssignment id value -> [ "conditionalIdentifier" .= id ] <> [ "value" .= value ]
S.Yield expr -> [ "yieldExpression" .= expr ]
- S.Until expr body -> [ "untilExpr" .= expr ] <> [ "untilBody" .= body ]
- S.Unless expr clauses -> [ "unless" .= expr ] <> childrenFields clauses
+ S.Negate expr -> [ "negate" .= expr ]
+ S.Rescue args expressions -> [ "args" .= args ] <> childrenFields expressions
where childrenFields c = [ "children" .= c ]
diff --git a/src/Renderer/Split.hs b/src/Renderer/Split.hs
index 8c0d2cd9f..3bc86c1c0 100644
--- a/src/Renderer/Split.hs
+++ b/src/Renderer/Split.hs
@@ -57,7 +57,7 @@ styleName category = "category-" <> case category of
TemplateString -> "template_string"
Regex -> "regex"
Identifier -> "identifier"
- Params -> "parameters"
+ C.Params -> "parameters"
ExpressionStatements -> "expression_statements"
C.MathAssignment -> "math_assignment"
C.SubscriptAccess -> "subscript_access"
@@ -89,6 +89,15 @@ styleName category = "category-" <> case category of
C.Yield -> "yield_statement"
C.Until -> "until"
C.Unless -> "unless_statement"
+ C.Begin -> "begin_statement"
+ C.Else -> "else_block"
+ C.Elsif -> "elsif_block"
+ C.Ensure -> "ensure_block"
+ C.Rescue -> "rescue_block"
+ C.RescueModifier -> "rescue_modifier"
+ C.When -> "when_block"
+ C.RescuedException -> "last_exception"
+ C.Negate -> "negate"
-- | Pick the class name for a split patch.
splitPatchToClassName :: SplitPatch a -> AttributeValue
diff --git a/src/Syntax.hs b/src/Syntax.hs
index 26d205450..e3763fb1f 100644
--- a/src/Syntax.hs
+++ b/src/Syntax.hs
@@ -36,9 +36,6 @@ data Syntax a f
-- | A method call consisting of its target, the method name, and the parameters passed to the method.
-- | e.g. in Javascript console.log('hello') represents a method call.
| MethodCall { targetId :: f, methodId :: f, methodParams :: [f] }
- -- | The list of arguments to a method call.
- -- | TODO: It might be worth removing this and using Fixed instead.
- | Args [f]
-- | An operator can be applied to a list of syntaxes.
| Operator [f]
-- | A variable declaration. e.g. var foo;
@@ -49,7 +46,7 @@ data Syntax a f
-- | e.g. in Javascript x["y"] represents a subscript access syntax.
| SubscriptAccess { subscriptId :: f, subscriptElement :: f }
| Switch { switchExpr :: f, cases :: [f] }
- | Case { caseExpr :: f, caseStatements :: f }
+ | Case { caseExpr :: f, caseStatements :: [f] }
| Object { keyValues :: [f] }
-- | A pair in an Object. e.g. foo: bar or foo => bar
| Pair f f
@@ -65,7 +62,8 @@ data Syntax a f
| Return (Maybe f)
| Throw f
| Constructor f
- | Try f (Maybe f) (Maybe f)
+ -- | TODO: Is it a problem that in Ruby, this pattern can work for method def too?
+ | Try { tryBegin :: [f], catchRescue :: [f], beginElse :: Maybe f, finallyEnsure :: Maybe f }
-- | An array literal with list of children.
| Array [f]
-- | A class with an identifier, superclass, and a list of definitions.
@@ -81,9 +79,10 @@ data Syntax a f
-- | A conditional assignment represents expressions whose operator classifies as conditional (e.g. ||= or &&=).
| ConditionalAssignment { conditionalAssignmentId :: f, value :: f }
| Yield (Maybe f)
- | Until { untilExpr :: f, untilBody :: [f] }
- -- | An unless statement with an expression and maybe more expression clauses.
- | Unless f [f]
+ -- | A negation of a single expression.
+ | Negate f
+ -- | A rescue block has a list of arguments to rescue and a list of expressions.
+ | Rescue [f] [f]
deriving (Eq, Foldable, Functor, Generic, Generic1, Mergeable, Ord, Show, Traversable, ToJSON)
diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json
index 240adb977..ab4c4cfe2 100644
--- a/test/corpus/diff-summaries/javascript/class.json
+++ b/test/corpus/diff-summaries/javascript/class.json
@@ -121,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'foo' identifier with the 'one' identifier in the one method of the 'Foo' class"
+ "summary": "Replaced the 'foo' identifier with the 'one' identifier in the 'one(a)' method of the 'Foo' class"
},
{
"span": {
@@ -136,7 +136,7 @@
]
}
},
- "summary": "Added the 'two' method in the Foo class"
+ "summary": "Added the 'two(b)' method in the Foo class"
},
{
"span": {
@@ -151,7 +151,7 @@
]
}
},
- "summary": "Added the 'three' method in the Foo class"
+ "summary": "Added the 'three(c)' method in the Foo class"
},
{
"span": {
@@ -166,7 +166,7 @@
]
}
},
- "summary": "Deleted the 'bar' method in the Foo class"
+ "summary": "Deleted the 'bar(b)' method in the Foo class"
},
{
"span": {
@@ -181,7 +181,7 @@
]
}
},
- "summary": "Deleted the 'baz' method in the Foo class"
+ "summary": "Deleted the 'baz(c)' method in the Foo class"
}
]
},
@@ -234,7 +234,7 @@
}
]
},
- "summary": "Replaced the 'one' identifier with the 'foo' identifier in the foo method of the 'Foo' class"
+ "summary": "Replaced the 'one' identifier with the 'foo' identifier in the 'foo(a)' method of the 'Foo' class"
},
{
"span": {
@@ -249,7 +249,7 @@
]
}
},
- "summary": "Added the 'bar' method in the Foo class"
+ "summary": "Added the 'bar(b)' method in the Foo class"
},
{
"span": {
@@ -264,7 +264,7 @@
]
}
},
- "summary": "Added the 'baz' method in the Foo class"
+ "summary": "Added the 'baz(c)' method in the Foo class"
},
{
"span": {
@@ -279,7 +279,7 @@
]
}
},
- "summary": "Deleted the 'two' method in the Foo class"
+ "summary": "Deleted the 'two(b)' method in the Foo class"
},
{
"span": {
@@ -294,7 +294,7 @@
]
}
},
- "summary": "Deleted the 'three' method in the Foo class"
+ "summary": "Deleted the 'three(c)' method in the Foo class"
}
]
},
diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json
index 1bfd7e468..2471cd96f 100644
--- a/test/corpus/diff-summaries/javascript/if-else.json
+++ b/test/corpus/diff-summaries/javascript/if-else.json
@@ -121,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'g' identifier with the 'x' identifier"
+ "summary": "Replaced the 'g' identifier with the 'x' identifier in the 'x' if statement"
},
{
"span": {
@@ -148,7 +148,7 @@
}
]
},
- "summary": "Replaced the 'h' identifier with the 'y' identifier"
+ "summary": "Replaced the 'h' identifier with the 'y' identifier in the 'x' if statement"
},
{
"span": {
@@ -175,7 +175,7 @@
}
]
},
- "summary": "Replaced the 'i' identifier with the 'a' identifier"
+ "summary": "Replaced the 'i' identifier with the 'a' identifier in the 'a' if statement"
},
{
"span": {
@@ -190,7 +190,7 @@
]
}
},
- "summary": "Added the 'b' identifier"
+ "summary": "Added the 'b' identifier in the 'a' if statement"
},
{
"span": {
@@ -205,7 +205,7 @@
]
}
},
- "summary": "Deleted the 'j' identifier"
+ "summary": "Deleted the 'j' identifier in the 'a' if statement"
},
{
"span": {
@@ -232,7 +232,7 @@
}
]
},
- "summary": "Replaced the 'k' identifier with the 'c' identifier"
+ "summary": "Replaced the 'k' identifier with the 'c' identifier in the 'c' if statement"
},
{
"span": {
@@ -259,7 +259,7 @@
}
]
},
- "summary": "Replaced the 'l' identifier with the 'd' identifier"
+ "summary": "Replaced the 'l' identifier with the 'd' identifier in the 'c' if statement"
},
{
"span": {
@@ -286,7 +286,7 @@
}
]
},
- "summary": "Replaced the 'm' identifier with the 'e' identifier"
+ "summary": "Replaced the 'm' identifier with the 'e' identifier in the 'e' if statement"
},
{
"span": {
@@ -301,7 +301,7 @@
]
}
},
- "summary": "Added the 'f' identifier"
+ "summary": "Added the 'f' identifier in the 'e' if statement"
},
{
"span": {
@@ -316,7 +316,7 @@
]
}
},
- "summary": "Deleted the 'n' identifier"
+ "summary": "Deleted the 'n' identifier in the 'e' if statement"
},
{
"span": {
@@ -343,7 +343,7 @@
}
]
},
- "summary": "Replaced the 'o' identifier with the 'g' identifier"
+ "summary": "Replaced the 'o' identifier with the 'g' identifier in the 'e' if statement"
}
]
},
@@ -396,7 +396,7 @@
}
]
},
- "summary": "Replaced the 'x' identifier with the 'g' identifier"
+ "summary": "Replaced the 'x' identifier with the 'g' identifier in the 'g' if statement"
},
{
"span": {
@@ -423,7 +423,7 @@
}
]
},
- "summary": "Replaced the 'y' identifier with the 'h' identifier"
+ "summary": "Replaced the 'y' identifier with the 'h' identifier in the 'g' if statement"
},
{
"span": {
@@ -450,7 +450,7 @@
}
]
},
- "summary": "Replaced the 'a' identifier with the 'i' identifier"
+ "summary": "Replaced the 'a' identifier with the 'i' identifier in the 'i' if statement"
},
{
"span": {
@@ -465,7 +465,7 @@
]
}
},
- "summary": "Added the 'j' identifier"
+ "summary": "Added the 'j' identifier in the 'i' if statement"
},
{
"span": {
@@ -480,7 +480,7 @@
]
}
},
- "summary": "Deleted the 'b' identifier"
+ "summary": "Deleted the 'b' identifier in the 'i' if statement"
},
{
"span": {
@@ -507,7 +507,7 @@
}
]
},
- "summary": "Replaced the 'c' identifier with the 'k' identifier"
+ "summary": "Replaced the 'c' identifier with the 'k' identifier in the 'k' if statement"
},
{
"span": {
@@ -534,7 +534,7 @@
}
]
},
- "summary": "Replaced the 'd' identifier with the 'l' identifier"
+ "summary": "Replaced the 'd' identifier with the 'l' identifier in the 'k' if statement"
},
{
"span": {
@@ -561,7 +561,7 @@
}
]
},
- "summary": "Replaced the 'e' identifier with the 'm' identifier"
+ "summary": "Replaced the 'e' identifier with the 'm' identifier in the 'm' if statement"
},
{
"span": {
@@ -576,7 +576,7 @@
]
}
},
- "summary": "Added the 'n' identifier"
+ "summary": "Added the 'n' identifier in the 'm' if statement"
},
{
"span": {
@@ -591,7 +591,7 @@
]
}
},
- "summary": "Deleted the 'f' identifier"
+ "summary": "Deleted the 'f' identifier in the 'm' if statement"
},
{
"span": {
@@ -618,7 +618,7 @@
}
]
},
- "summary": "Replaced the 'g' identifier with the 'o' identifier"
+ "summary": "Replaced the 'g' identifier with the 'o' identifier in the 'm' if statement"
}
]
},
diff --git a/test/corpus/diff-summaries/javascript/objects-with-methods.json b/test/corpus/diff-summaries/javascript/objects-with-methods.json
index 0667db2ad..33feda07d 100644
--- a/test/corpus/diff-summaries/javascript/objects-with-methods.json
+++ b/test/corpus/diff-summaries/javascript/objects-with-methods.json
@@ -16,7 +16,7 @@
]
}
},
- "summary": "Added the '{ add }' object"
+ "summary": "Added the '{ add(a, b) }' object"
}
]
},
@@ -54,7 +54,7 @@
]
}
},
- "summary": "Added the '{ subtract }' object"
+ "summary": "Added the '{ subtract(a, b) }' object"
},
{
"span": {
@@ -69,7 +69,7 @@
]
}
},
- "summary": "Added the '{ add }' object"
+ "summary": "Added the '{ add(a, b) }' object"
}
]
},
@@ -121,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'subtract' identifier with the 'add' identifier in the add method"
+ "summary": "Replaced the 'subtract' identifier with the 'add' identifier in the 'add(a, b)' method"
}
]
},
@@ -174,7 +174,7 @@
}
]
},
- "summary": "Replaced the 'add' identifier with the 'subtract' identifier in the subtract method"
+ "summary": "Replaced the 'add' identifier with the 'subtract' identifier in the 'subtract(a, b)' method"
}
]
},
@@ -215,7 +215,7 @@
]
}
},
- "summary": "Deleted the '{ subtract }' object"
+ "summary": "Deleted the '{ subtract(a, b) }' object"
},
{
"span": {
@@ -230,7 +230,7 @@
]
}
},
- "summary": "Deleted the '{ add }' object"
+ "summary": "Deleted the '{ add(a, b) }' object"
},
{
"span": {
@@ -245,7 +245,7 @@
]
}
},
- "summary": "Added the '{ subtract }' object"
+ "summary": "Added the '{ subtract(a, b) }' object"
}
]
},
@@ -286,7 +286,7 @@
]
}
},
- "summary": "Deleted the '{ add }' object"
+ "summary": "Deleted the '{ add(a, b) }' object"
}
]
},
@@ -325,7 +325,7 @@
]
}
},
- "summary": "Deleted the '{ subtract }' object"
+ "summary": "Deleted the '{ subtract(a, b) }' object"
}
]
},
diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json
index 2fcf6ff37..9bd205100 100644
--- a/test/corpus/diff-summaries/javascript/switch-statement.json
+++ b/test/corpus/diff-summaries/javascript/switch-statement.json
@@ -121,7 +121,7 @@
}
]
},
- "summary": "Replaced '2' with '1'"
+ "summary": "Replaced '2' with '1' in the '1' switch statement"
},
{
"span": {
@@ -148,7 +148,7 @@
}
]
},
- "summary": "Replaced '2' with '1'"
+ "summary": "Replaced '2' with '1' in the '2' case statement"
}
]
},
@@ -201,7 +201,7 @@
}
]
},
- "summary": "Replaced '1' with '2'"
+ "summary": "Replaced '1' with '2' in the '2' switch statement"
},
{
"span": {
@@ -228,7 +228,7 @@
}
]
},
- "summary": "Replaced '1' with '2'"
+ "summary": "Replaced '1' with '2' in the '2' case statement"
}
]
},
diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json
index 7c9a683c3..80e94c7ff 100644
--- a/test/corpus/diff-summaries/javascript/try-statement.json
+++ b/test/corpus/diff-summaries/javascript/try-statement.json
@@ -121,7 +121,7 @@
}
]
},
- "summary": "Replaced the 'h' identifier with the 'g' identifier"
+ "summary": "Replaced the 'h' identifier with the 'g' identifier in the { f; } try statement"
},
{
"span": {
@@ -148,7 +148,7 @@
}
]
},
- "summary": "Replaced the 'g' identifier with the 'h' identifier"
+ "summary": "Replaced the 'g' identifier with the 'h' identifier in the { f; } try statement"
}
]
},
@@ -201,7 +201,7 @@
}
]
},
- "summary": "Replaced the 'g' identifier with the 'h' identifier"
+ "summary": "Replaced the 'g' identifier with the 'h' identifier in the { f; } try statement"
},
{
"span": {
@@ -228,7 +228,7 @@
}
]
},
- "summary": "Replaced the 'h' identifier with the 'g' identifier"
+ "summary": "Replaced the 'h' identifier with the 'g' identifier in the { f; } try statement"
}
]
},
diff --git a/test/corpus/diff-summaries/ruby/and-or.json b/test/corpus/diff-summaries/ruby/and-or.json
index 05f75246c..3f555ae25 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": "b97d4839e17a24809828d9e91c9b126bcd4a7539..27c9a357ee145ca54a29f536970996688e8de6e1"
+ "shas": "c7d3f438c72d2ab2a09e3fa47ba1cf9b175d2a9b..0bc5f86f8c781f501003b94889818004364037b9"
}
,{
"testCaseDescription": "ruby-and-or-replacement-insert-test",
@@ -105,7 +105,7 @@
" foo and bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "27c9a357ee145ca54a29f536970996688e8de6e1..a303976a68f3edc659fe0e0c99361750fdd8ee8d"
+ "shas": "0bc5f86f8c781f501003b94889818004364037b9..2c06275827cfa3bbaada5117072cd19574d8d7a9"
}
,{
"testCaseDescription": "ruby-and-or-delete-insert-test",
@@ -147,7 +147,7 @@
" foo and bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a303976a68f3edc659fe0e0c99361750fdd8ee8d..ce07447cbe8aee84e85560cf6b51d168ae3be40e"
+ "shas": "2c06275827cfa3bbaada5117072cd19574d8d7a9..e800a12b636011a03bc99b86835317cd7ad3ecd1"
}
,{
"testCaseDescription": "ruby-and-or-replacement-test",
@@ -189,7 +189,7 @@
" foo and bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ce07447cbe8aee84e85560cf6b51d168ae3be40e..7259fbbdc8f4e75358e9b1072dd808570924b862"
+ "shas": "e800a12b636011a03bc99b86835317cd7ad3ecd1..c9340cbb8ada35c896fa285761dd0e9dac96fd0b"
}
,{
"testCaseDescription": "ruby-and-or-delete-replacement-test",
@@ -261,7 +261,7 @@
"-foo and bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7259fbbdc8f4e75358e9b1072dd808570924b862..b674c1b31620b093f57097c094c8088f3a5679c5"
+ "shas": "c9340cbb8ada35c896fa285761dd0e9dac96fd0b..66224b27113350bc8e9d7ffddc2fe22fee05baa2"
}
,{
"testCaseDescription": "ruby-and-or-delete-test",
@@ -301,7 +301,7 @@
" a or b and c"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b674c1b31620b093f57097c094c8088f3a5679c5..66ac8a3e81a008110bda22b7d07ba4840f36081e"
+ "shas": "66224b27113350bc8e9d7ffddc2fe22fee05baa2..22157102e33b0c6c91eed738c3c7a3ce0edc3fa7"
}
,{
"testCaseDescription": "ruby-and-or-delete-rest-test",
@@ -355,5 +355,5 @@
"-a or b and c"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "66ac8a3e81a008110bda22b7d07ba4840f36081e..67c2202d60f5cb8661e9fd99d9488cfc61c51656"
+ "shas": "22157102e33b0c6c91eed738c3c7a3ce0edc3fa7..956b136e24f76c977fefd27d5368ecd527f721ec"
}]
diff --git a/test/corpus/diff-summaries/ruby/array.json b/test/corpus/diff-summaries/ruby/array.json
index 43688e6d3..279a9c36f 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": "e7484e4c64ba50c6ce9673390ee4533e86e78aaf..e7c918141e0259db3457897c2f9cc39122fb4dfa"
+ "shas": "e8c4c9b4ba151237a0e88d5a650d34ee5a5a1b61..92505afbaea485d23aecf7f8edb66dfad7e17fd8"
}
,{
"testCaseDescription": "ruby-array-replacement-insert-test",
@@ -89,7 +89,7 @@
" [ 1, 2, 3]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e7c918141e0259db3457897c2f9cc39122fb4dfa..2d418c50602823813d17c0ffbb653f4c41964cea"
+ "shas": "92505afbaea485d23aecf7f8edb66dfad7e17fd8..4f3473df5291027b89f3b4fe9ca1854e49454cc4"
}
,{
"testCaseDescription": "ruby-array-delete-insert-test",
@@ -205,7 +205,7 @@
" [ 1, 2, 3]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2d418c50602823813d17c0ffbb653f4c41964cea..b41922c03602426b090d745fc831476ce4273f28"
+ "shas": "4f3473df5291027b89f3b4fe9ca1854e49454cc4..9def16756eb5f54b2e6b55b6a4cdfeb4a8d5de46"
}
,{
"testCaseDescription": "ruby-array-replacement-test",
@@ -321,7 +321,7 @@
" [ 1, 2, 3]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b41922c03602426b090d745fc831476ce4273f28..90dbd65e730eca5d684767eb015e91d64852516b"
+ "shas": "9def16756eb5f54b2e6b55b6a4cdfeb4a8d5de46..201d96f51f94a1a40acc9278b6adc775bea84b0f"
}
,{
"testCaseDescription": "ruby-array-delete-replacement-test",
@@ -392,7 +392,7 @@
"+['a', 'b', 'c']"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "90dbd65e730eca5d684767eb015e91d64852516b..99450e05ccc1623be6fd3e6055600f04019e903e"
+ "shas": "201d96f51f94a1a40acc9278b6adc775bea84b0f..b5284048ab1c80b398b60b7c632c733adde8df2e"
}
,{
"testCaseDescription": "ruby-array-delete-test",
@@ -431,7 +431,7 @@
" ['a', 'b', 'c']"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "99450e05ccc1623be6fd3e6055600f04019e903e..db6171b1e65fc9ba97375c98fa57b9f8730e39f8"
+ "shas": "b5284048ab1c80b398b60b7c632c733adde8df2e..aff7086bf8fd3b7fc3be8f3bd49c41c46a049729"
}
,{
"testCaseDescription": "ruby-array-delete-rest-test",
@@ -469,5 +469,5 @@
"-['a', 'b', 'c']"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "db6171b1e65fc9ba97375c98fa57b9f8730e39f8..698867032f63fc98f3b15d9fd3e752171ef9b0ca"
+ "shas": "aff7086bf8fd3b7fc3be8f3bd49c41c46a049729..79b196cace027a076f4ba235171fd4f409bdaba9"
}]
diff --git a/test/corpus/diff-summaries/ruby/assignment.json b/test/corpus/diff-summaries/ruby/assignment.json
index b12eaa05a..b6905929e 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": "57f86efa1b5bea006e86c9d582280c3e622cb4ea..f08d8aa1003ac043ff916cefeb4df511fb41e099"
+ "shas": "4d0ef41f7debeacebe9a218e39bb2b48c8405446..ad5a90e438df179af24b1db62954dd57456ecb70"
}
,{
"testCaseDescription": "ruby-assignment-replacement-insert-test",
@@ -89,7 +89,7 @@
" x = 0"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f08d8aa1003ac043ff916cefeb4df511fb41e099..9a88d58eb0721119c25aac22df3d741c50794e27"
+ "shas": "ad5a90e438df179af24b1db62954dd57456ecb70..91faac962a01a884edd6ada891ced7040d038ad4"
}
,{
"testCaseDescription": "ruby-assignment-delete-insert-test",
@@ -142,7 +142,7 @@
" x = 0"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9a88d58eb0721119c25aac22df3d741c50794e27..d1ff964100006298196b1858b33596356679b74b"
+ "shas": "91faac962a01a884edd6ada891ced7040d038ad4..9176406da7e16de7c17eddfbeb557a7441dcae6b"
}
,{
"testCaseDescription": "ruby-assignment-replacement-test",
@@ -195,7 +195,7 @@
" x = 0"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d1ff964100006298196b1858b33596356679b74b..a6e5ae47e403bc29de6460c50ace19d1eef00aa8"
+ "shas": "9176406da7e16de7c17eddfbeb557a7441dcae6b..781f04eca397646ee7614b9206aa7eff79a2e400"
}
,{
"testCaseDescription": "ruby-assignment-delete-replacement-test",
@@ -266,7 +266,7 @@
"+x = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a6e5ae47e403bc29de6460c50ace19d1eef00aa8..14a96448f85cbe57c7e0ddf95454aba657c6931b"
+ "shas": "781f04eca397646ee7614b9206aa7eff79a2e400..75bccc3232c4b4773225c70ba35b08ba08e95d38"
}
,{
"testCaseDescription": "ruby-assignment-delete-test",
@@ -305,7 +305,7 @@
" x = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "14a96448f85cbe57c7e0ddf95454aba657c6931b..541105badde89f9f61723eb06d211d4c45ec0138"
+ "shas": "75bccc3232c4b4773225c70ba35b08ba08e95d38..5dd9958c7bc7d5736ba816f77ce0a88f7b2fa709"
}
,{
"testCaseDescription": "ruby-assignment-delete-rest-test",
@@ -343,5 +343,5 @@
"-x = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "541105badde89f9f61723eb06d211d4c45ec0138..6b7b3f3ff94314a6d7e0047cab6161b417c272bf"
+ "shas": "5dd9958c7bc7d5736ba816f77ce0a88f7b2fa709..a07f2fef830bc79ffa2136025c4e29d5c8a0ff1b"
}]
diff --git a/test/corpus/diff-summaries/ruby/begin.json b/test/corpus/diff-summaries/ruby/begin.json
new file mode 100644
index 000000000..89beda515
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/begin.json
@@ -0,0 +1,244 @@
+[{
+ "testCaseDescription": "ruby-begin-setup-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index e69de29..ff7bbbe 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -0,0 +1,2 @@",
+ "+def foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "72e1f4912f54a936266422abbb53a9c2fc864992..d9be702e11b41377baa2f5fb3ccd4e3cf3dd81e4"
+}
+,{
+ "testCaseDescription": "ruby-begin-insert-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement in the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index ff7bbbe..7b4a3be 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -1,2 +1,4 @@",
+ " def foo",
+ "+begin",
+ "+end",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d9be702e11b41377baa2f5fb3ccd4e3cf3dd81e4..1f7c992ecbf8dc5434ec7da2bc396e814e91adc9"
+}
+,{
+ "testCaseDescription": "ruby-begin-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'puts('hi')' function call in a begin statement of the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index 7b4a3be..7879e55 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -1,4 +1,5 @@",
+ " def foo",
+ " begin",
+ "+ puts 'hi'",
+ " end",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1f7c992ecbf8dc5434ec7da2bc396e814e91adc9..a72bbedc16a6b300edf51b665ebaf90e62662ab8"
+}
+,{
+ "testCaseDescription": "ruby-begin-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 12
+ ]
+ }
+ },
+ "summary": "Deleted the 'puts('hi')' function call in a begin statement of the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index 7879e55..7b4a3be 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -1,5 +1,4 @@",
+ " def foo",
+ " begin",
+ "- puts 'hi'",
+ " end",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "a72bbedc16a6b300edf51b665ebaf90e62662ab8..4ba57f34c39daab00f1b9fc48f1e162ced2e9a44"
+}
+,{
+ "testCaseDescription": "ruby-begin-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement in the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index 7b4a3be..ff7bbbe 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -1,4 +1,2 @@",
+ " def foo",
+ "-begin",
+ "-end",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "4ba57f34c39daab00f1b9fc48f1e162ced2e9a44..9995f52897de0441895de23887b80cd4c9b7ea75"
+}
+,{
+ "testCaseDescription": "ruby-begin-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "begin.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "begin.rb"
+ ],
+ "patch": [
+ "diff --git a/begin.rb b/begin.rb",
+ "index ff7bbbe..e69de29 100644",
+ "--- a/begin.rb",
+ "+++ b/begin.rb",
+ "@@ -1,2 +0,0 @@",
+ "-def foo",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "9995f52897de0441895de23887b80cd4c9b7ea75..cc81318f97e858789ab75eb6e9c4a9ef9a96807c"
+}]
diff --git a/test/corpus/diff-summaries/ruby/bitwise-operator.json b/test/corpus/diff-summaries/ruby/bitwise-operator.json
index 359301b51..8508f6bda 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": "31802ff35f32594a6c786a0a16272451c84d2bbf..3b62c609e123b9b7605fa78affe04fc056ab4206"
+ "shas": "70d36a6a9817b1e91707c1f7f830a0568b959efa..ce65ef18e5032a270bbfcef7d593c68d270abaf4"
}
,{
"testCaseDescription": "ruby-bitwise-operator-replacement-insert-test",
@@ -171,7 +171,7 @@
" a ^ b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3b62c609e123b9b7605fa78affe04fc056ab4206..52ddee1b885a5663409865e7f974ba18c32cfbbe"
+ "shas": "ce65ef18e5032a270bbfcef7d593c68d270abaf4..3710a2840202f8625b9a440d8b556a6d30d2b6f6"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-insert-test",
@@ -216,7 +216,7 @@
" a ^ b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "52ddee1b885a5663409865e7f974ba18c32cfbbe..d817350d9211fef522618f2ff453034b26f46f6a"
+ "shas": "3710a2840202f8625b9a440d8b556a6d30d2b6f6..88289eb5fde1222a010efda881ce7888c282fe61"
}
,{
"testCaseDescription": "ruby-bitwise-operator-replacement-test",
@@ -261,7 +261,7 @@
" a ^ b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d817350d9211fef522618f2ff453034b26f46f6a..ac4c606315b63689a5400b43c6585076507be085"
+ "shas": "88289eb5fde1222a010efda881ce7888c282fe61..5ae589defd184d837cb3d384ab225f42299801d8"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-replacement-test",
@@ -338,7 +338,7 @@
"+a << b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ac4c606315b63689a5400b43c6585076507be085..a534b432e76cb0a4efd4dd60705023d2ff883975"
+ "shas": "5ae589defd184d837cb3d384ab225f42299801d8..29cf76ea1e49cdef2e616fed189fec268693ca87"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-test",
@@ -410,7 +410,7 @@
" a << b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a534b432e76cb0a4efd4dd60705023d2ff883975..1488c67e01dbda92b51afbb283841c4888365131"
+ "shas": "29cf76ea1e49cdef2e616fed189fec268693ca87..4bb4fee464aeaf7f957b7750b0947e7c02f2a8a8"
}
,{
"testCaseDescription": "ruby-bitwise-operator-delete-rest-test",
@@ -464,5 +464,5 @@
"-a << b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1488c67e01dbda92b51afbb283841c4888365131..6436c88397ac50ad9fd8cf92b759ac75806d2f73"
+ "shas": "4bb4fee464aeaf7f957b7750b0947e7c02f2a8a8..8b196e55798c1a5f125a87a869f770dca83665d6"
}]
diff --git a/test/corpus/diff-summaries/ruby/boolean-operator.json b/test/corpus/diff-summaries/ruby/boolean-operator.json
index 5b94a8406..754aa298f 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": "b06f33881ef5a8d65535fc5f044cddf24ff1033a..9d4e3097b545474c0c1693984bb6c2e8b7c8c1f0"
+ "shas": "5b279526f66afb77b2588f5173ce44d7cc693f97..53ec9b4615b8872e47ba643814f579eb3d74ef32"
}
,{
"testCaseDescription": "ruby-boolean-operator-replacement-insert-test",
@@ -89,7 +89,7 @@
" a || b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9d4e3097b545474c0c1693984bb6c2e8b7c8c1f0..9bca9d5aea1f9aae86458271deba3d2b81e2076e"
+ "shas": "53ec9b4615b8872e47ba643814f579eb3d74ef32..02c804c5e37002a6843f3fc329c5db03ad4d51f6"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-insert-test",
@@ -112,7 +112,7 @@
" a || b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9bca9d5aea1f9aae86458271deba3d2b81e2076e..b10c305636f3b3fd9a85d24183e403cc45e84b9e"
+ "shas": "02c804c5e37002a6843f3fc329c5db03ad4d51f6..144d5b79b707781d8b5d1d56e281bcaa8598ae17"
}
,{
"testCaseDescription": "ruby-boolean-operator-replacement-test",
@@ -135,7 +135,7 @@
" a || b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b10c305636f3b3fd9a85d24183e403cc45e84b9e..6faff89bdb6145160ac5383775c741e7e9cd54c5"
+ "shas": "144d5b79b707781d8b5d1d56e281bcaa8598ae17..000c0198a566086df4d95a1ffd575748b7721552"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-replacement-test",
@@ -176,7 +176,7 @@
"+a && b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6faff89bdb6145160ac5383775c741e7e9cd54c5..cc135495b8b557bf028f841f0d25c27a220049c2"
+ "shas": "000c0198a566086df4d95a1ffd575748b7721552..f363216d5459fb0eafeb0168cc3f4af6d11f8cd5"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-test",
@@ -215,7 +215,7 @@
" a && b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cc135495b8b557bf028f841f0d25c27a220049c2..d719fc6849041f23a3787726c6ae0a14bb6deba7"
+ "shas": "f363216d5459fb0eafeb0168cc3f4af6d11f8cd5..57a8c0847390f2f78910231321007d7b2c86cc7a"
}
,{
"testCaseDescription": "ruby-boolean-operator-delete-rest-test",
@@ -253,5 +253,5 @@
"-a && b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d719fc6849041f23a3787726c6ae0a14bb6deba7..cdfe07e3ce652a0ca3282e6fb45641f687c90cc9"
+ "shas": "57a8c0847390f2f78910231321007d7b2c86cc7a..0c8195a0d30149b84b53bc2c98687d24a787f4dd"
}]
diff --git a/test/corpus/diff-summaries/ruby/class.json b/test/corpus/diff-summaries/ruby/class.json
index 3e7698c4f..e62e83f4d 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": "c6b6465d210afae65e64e64da1f92884d63ad7d9..4a7c2666650b79a751a59f1566d4bf85a6d15f5b"
+ "shas": "98200bee05decb871fcfdf6858ee954898880f72..b6210fce75b001a4f6dcebfd8977c41c74c55e40"
}
,{
"testCaseDescription": "ruby-class-replacement-insert-test",
@@ -97,7 +97,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4a7c2666650b79a751a59f1566d4bf85a6d15f5b..8d2f76f7fe9816e4cc6a8dd840fe0ede6923bd1e"
+ "shas": "b6210fce75b001a4f6dcebfd8977c41c74c55e40..4d8c5346eda3e267a62cbe1cd2da74ff24035f5b"
}
,{
"testCaseDescription": "ruby-class-delete-insert-test",
@@ -121,7 +121,7 @@
" class Foo < Super"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8d2f76f7fe9816e4cc6a8dd840fe0ede6923bd1e..0b6610d9514245ad667de7a2117d30a38ac6c563"
+ "shas": "4d8c5346eda3e267a62cbe1cd2da74ff24035f5b..895b7645a3ad8b26bfb59f814bf914213a1508f8"
}
,{
"testCaseDescription": "ruby-class-replacement-test",
@@ -145,7 +145,7 @@
" class Foo < Super"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0b6610d9514245ad667de7a2117d30a38ac6c563..650f2504ace9e91709433e8f4e18a168038770ad"
+ "shas": "895b7645a3ad8b26bfb59f814bf914213a1508f8..64fd047eef7b0ce2ea5e8746e8d79b3ca8c0ec06"
}
,{
"testCaseDescription": "ruby-class-delete-replacement-test",
@@ -222,7 +222,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "650f2504ace9e91709433e8f4e18a168038770ad..a4eb5b62dcb95470f072ec3b4fb8c0e132e5f358"
+ "shas": "64fd047eef7b0ce2ea5e8746e8d79b3ca8c0ec06..129ea7453ad876f91980fe45c08f65586d0b082b"
}
,{
"testCaseDescription": "ruby-class-delete-test",
@@ -265,7 +265,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a4eb5b62dcb95470f072ec3b4fb8c0e132e5f358..f0cf181a0aa6f3568b4df1fef8955373186bfe8e"
+ "shas": "129ea7453ad876f91980fe45c08f65586d0b082b..7a054e58466e2a33d7c70bb948497f3b0622b6e5"
}
,{
"testCaseDescription": "ruby-class-delete-rest-test",
@@ -305,5 +305,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f0cf181a0aa6f3568b4df1fef8955373186bfe8e..daa964737173b38b4dd562e5d4370fe48ccba4f6"
+ "shas": "7a054e58466e2a33d7c70bb948497f3b0622b6e5..5e4ebb1f424a9e273ffc7cc40c76cee1d78b0d77"
}]
diff --git a/test/corpus/diff-summaries/ruby/comment.json b/test/corpus/diff-summaries/ruby/comment.json
index a77f02734..00c9e9eb8 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": "6b7b3f3ff94314a6d7e0047cab6161b417c272bf..a284722762b0dd952426e5dfc01ebba2d2ff1a8f"
+ "shas": "a07f2fef830bc79ffa2136025c4e29d5c8a0ff1b..d3d916a02cf198fb7c5c5f96df6b1fc4382b76e8"
}
,{
"testCaseDescription": "ruby-comment-replacement-insert-test",
@@ -41,7 +41,7 @@
" # This is a comment"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a284722762b0dd952426e5dfc01ebba2d2ff1a8f..2852a24714a1e635ce417d791ad750873ed08ae9"
+ "shas": "d3d916a02cf198fb7c5c5f96df6b1fc4382b76e8..f7b133e4dd896586ba44964a6d2bd39a6127add3"
}
,{
"testCaseDescription": "ruby-comment-delete-insert-test",
@@ -67,7 +67,7 @@
" # This is a comment"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2852a24714a1e635ce417d791ad750873ed08ae9..e4a6fcaedd49358dccd560f68cc14bf24a5d5a80"
+ "shas": "f7b133e4dd896586ba44964a6d2bd39a6127add3..0a2c056dcc8f63a3911048c316c580cf4252efc7"
}
,{
"testCaseDescription": "ruby-comment-replacement-test",
@@ -93,7 +93,7 @@
" # This is a comment"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e4a6fcaedd49358dccd560f68cc14bf24a5d5a80..5f3f4b6c9a64b6fcd80b85c36106f9128163d930"
+ "shas": "0a2c056dcc8f63a3911048c316c580cf4252efc7..bf6bbf3aa85c998bbea81e8fcd8c51057e9a843c"
}
,{
"testCaseDescription": "ruby-comment-delete-replacement-test",
@@ -119,7 +119,7 @@
"-# This is a comment"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5f3f4b6c9a64b6fcd80b85c36106f9128163d930..30a93ec4c496f17a7adfdd5bfb918e5202437730"
+ "shas": "bf6bbf3aa85c998bbea81e8fcd8c51057e9a843c..c7b39074cc7505098417f848da30325ca8b7410f"
}
,{
"testCaseDescription": "ruby-comment-delete-test",
@@ -142,7 +142,7 @@
" comment"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "30a93ec4c496f17a7adfdd5bfb918e5202437730..1b2efe12e0975594889854cda1c03e6cfeff86a9"
+ "shas": "c7b39074cc7505098417f848da30325ca8b7410f..ef695b264a83cfc43b8b08eb4bfcd4f22fa138d1"
}
,{
"testCaseDescription": "ruby-comment-delete-rest-test",
@@ -165,5 +165,5 @@
"-=end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1b2efe12e0975594889854cda1c03e6cfeff86a9..89de1fd8cc6322c451fec05b9e25888a290fb45b"
+ "shas": "ef695b264a83cfc43b8b08eb4bfcd4f22fa138d1..0f08e943de503b5d714186206425966f0517ddec"
}]
diff --git a/test/corpus/diff-summaries/ruby/comparision-operator.json b/test/corpus/diff-summaries/ruby/comparision-operator.json
index 5f19bda89..1c6c8b5a8 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": "cba823072c13adb125530eb20fdcce1c84bb71e4..c13eedbea577eba5c66da735a8384de068e9cb12"
+ "shas": "cc9a4a6fa2a1c65983250a900daf6501538b4cd8..d0eb4857f83d5eef8c789d9b1800947161d8876d"
}
,{
"testCaseDescription": "ruby-comparision-operator-replacement-insert-test",
@@ -138,7 +138,7 @@
" a > b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c13eedbea577eba5c66da735a8384de068e9cb12..1175a728e7fe039dad516edeaabf1c98d3c58bf5"
+ "shas": "d0eb4857f83d5eef8c789d9b1800947161d8876d..186f6c1cb9c2260246f3126b1203b54b9670ea09"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-insert-test",
@@ -164,7 +164,7 @@
" x < y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1175a728e7fe039dad516edeaabf1c98d3c58bf5..fc6a867417b84dfe67655ef3134d5e6eb5569043"
+ "shas": "186f6c1cb9c2260246f3126b1203b54b9670ea09..4e7370cd85c7f324871137855a459a1c583bce75"
}
,{
"testCaseDescription": "ruby-comparision-operator-replacement-test",
@@ -190,7 +190,7 @@
" x < y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fc6a867417b84dfe67655ef3134d5e6eb5569043..6e33eea47b9a1409ef2b4e9ae1c69ef787013b99"
+ "shas": "4e7370cd85c7f324871137855a459a1c583bce75..a26bfabeda46c054da38b6aaf5564c5b9e575294"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-replacement-test",
@@ -250,7 +250,7 @@
"+a >= b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6e33eea47b9a1409ef2b4e9ae1c69ef787013b99..a1d851f74f03f480e76cef11465d083169de41a5"
+ "shas": "a26bfabeda46c054da38b6aaf5564c5b9e575294..0e4db6b78d0c970ab1b1c30a357997ccd2dd80fa"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-test",
@@ -306,7 +306,7 @@
" a >= b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a1d851f74f03f480e76cef11465d083169de41a5..409a9b0991350430ff0f606dd617511bf57c3905"
+ "shas": "0e4db6b78d0c970ab1b1c30a357997ccd2dd80fa..84a86501aebef11b8627b8524fc8d324665ffc44"
}
,{
"testCaseDescription": "ruby-comparision-operator-delete-rest-test",
@@ -360,5 +360,5 @@
"-a >= b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "409a9b0991350430ff0f606dd617511bf57c3905..31802ff35f32594a6c786a0a16272451c84d2bbf"
+ "shas": "84a86501aebef11b8627b8524fc8d324665ffc44..70d36a6a9817b1e91707c1f7f830a0568b959efa"
}]
diff --git a/test/corpus/diff-summaries/ruby/conditional-assignment.json b/test/corpus/diff-summaries/ruby/conditional-assignment.json
index 348f2bd46..25744554c 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": "d75e597048bd0cbd98f3281d4924a665368b14d3..2771417f3a1ca7df7b88d04643584b83c7026244"
+ "shas": "6564c9c8832540d910a4118a6130305613ef9772..737bffe1cb105e55eb30dcb5e66499a162216c4d"
}
,{
"testCaseDescription": "ruby-conditional-assignment-replacement-insert-test",
@@ -89,7 +89,7 @@
" x ||= 5"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2771417f3a1ca7df7b88d04643584b83c7026244..64a8092553a96a12f2c25e1862700704aa04501e"
+ "shas": "737bffe1cb105e55eb30dcb5e66499a162216c4d..b4680d4032610561ef31cbb0508bfc9573be0d0c"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-insert-test",
@@ -142,7 +142,7 @@
" x ||= 5"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "64a8092553a96a12f2c25e1862700704aa04501e..b7b20fcc082178d0bc5830ef4c57f19e93f27d02"
+ "shas": "b4680d4032610561ef31cbb0508bfc9573be0d0c..cce1693dd4e7b6101f7cbcc9100b4c3276194fa2"
}
,{
"testCaseDescription": "ruby-conditional-assignment-replacement-test",
@@ -195,7 +195,7 @@
" x ||= 5"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b7b20fcc082178d0bc5830ef4c57f19e93f27d02..d8a975b6776279b4e557a0f3a32b53d0cc71b80f"
+ "shas": "cce1693dd4e7b6101f7cbcc9100b4c3276194fa2..8bd810b4f976b9701ff7a0ceb9d018bfeac4780e"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-replacement-test",
@@ -266,7 +266,7 @@
"+x &&= 7"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d8a975b6776279b4e557a0f3a32b53d0cc71b80f..1171aab0dc925f7f9f929f4057590e6a1d333438"
+ "shas": "8bd810b4f976b9701ff7a0ceb9d018bfeac4780e..ddc2e0154b1f8cbb3c3e3800549d0c5126c7ff52"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-test",
@@ -305,7 +305,7 @@
" x &&= 7"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1171aab0dc925f7f9f929f4057590e6a1d333438..9cff4a6c0247d0025648efa52c6b48e0e7b08b9c"
+ "shas": "ddc2e0154b1f8cbb3c3e3800549d0c5126c7ff52..4f41d6075e03521d205fb38e22fe31e8f89ffcd9"
}
,{
"testCaseDescription": "ruby-conditional-assignment-delete-rest-test",
@@ -343,5 +343,5 @@
"-x &&= 7"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9cff4a6c0247d0025648efa52c6b48e0e7b08b9c..ae7f80931d5929403f69e872bbbb5459015f485d"
+ "shas": "4f41d6075e03521d205fb38e22fe31e8f89ffcd9..78a9116b77a62e27008d72a5a1f2b1b9bec795bd"
}]
diff --git a/test/corpus/diff-summaries/ruby/delimiter.json b/test/corpus/diff-summaries/ruby/delimiter.json
index 55caba2b7..4287293ac 100644
--- a/test/corpus/diff-summaries/ruby/delimiter.json
+++ b/test/corpus/diff-summaries/ruby/delimiter.json
@@ -114,7 +114,7 @@
"+%Qc>"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1e20280b6e0ca3be21fcf83476fcda56c9883d3b..299d43ea2d4bf29d0b05d5c2a19f827e7931bc85"
+ "shas": "ef8d34476c23317120bf744df9d41b9110a04c03..1b0f7afd8b56c527a93bcf77cd130a197736aae8"
}
,{
"testCaseDescription": "ruby-delimiter-replacement-insert-test",
@@ -331,7 +331,7 @@
" %#a#"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "299d43ea2d4bf29d0b05d5c2a19f827e7931bc85..f342451a6757c26eb3ae5a35f179354ead5aa8e5"
+ "shas": "1b0f7afd8b56c527a93bcf77cd130a197736aae8..4e8d0a2cbe3dfca073f23bbb72b1461e5963338e"
}
,{
"testCaseDescription": "ruby-delimiter-delete-insert-test",
@@ -545,7 +545,7 @@
" %#a#"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f342451a6757c26eb3ae5a35f179354ead5aa8e5..cea8fa03e4e3b652d1112cf1e17d40ccdea94880"
+ "shas": "4e8d0a2cbe3dfca073f23bbb72b1461e5963338e..413fa9f465cd1591ad3c753e6d5d160ac0503019"
}
,{
"testCaseDescription": "ruby-delimiter-replacement-test",
@@ -753,7 +753,7 @@
" %#a#"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cea8fa03e4e3b652d1112cf1e17d40ccdea94880..5c5d602d9a7e1b860cab5c354438ba90716b1f1d"
+ "shas": "413fa9f465cd1591ad3c753e6d5d160ac0503019..2a8902902ea697fda4a67838615f8b6a8e108353"
}
,{
"testCaseDescription": "ruby-delimiter-delete-replacement-test",
@@ -1069,7 +1069,7 @@
"+%Q{d{e}f}"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5c5d602d9a7e1b860cab5c354438ba90716b1f1d..ac4230a762220d14aa360c21c28bc580745f8af7"
+ "shas": "2a8902902ea697fda4a67838615f8b6a8e108353..c03569b5f580bc90dc6d65cdd1ec2c719444ce89"
}
,{
"testCaseDescription": "ruby-delimiter-delete-test",
@@ -1190,7 +1190,7 @@
" %/b/"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ac4230a762220d14aa360c21c28bc580745f8af7..6e79cb3ff135e2c99d78d016e6531ee60e3e15a8"
+ "shas": "c03569b5f580bc90dc6d65cdd1ec2c719444ce89..e9178c14220997160dfe6c89506972e0b7e1f258"
}
,{
"testCaseDescription": "ruby-delimiter-delete-rest-test",
@@ -1308,5 +1308,5 @@
"-%Q{d{e}f}"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6e79cb3ff135e2c99d78d016e6531ee60e3e15a8..5027b0f8c8dc6adc15ff46a34a91777cc5ca4d7e"
+ "shas": "e9178c14220997160dfe6c89506972e0b7e1f258..b8a1e5f549bc1fa5a1424093d499d32fa0987cee"
}]
diff --git a/test/corpus/diff-summaries/ruby/element-reference.json b/test/corpus/diff-summaries/ruby/element-reference.json
index 60c5258ee..081f3f9a7 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": "99365feb6db5e2496cd89fea86b04d3d155dbba8..9df6e5ca2983e03c49491c3406b07d340e9fefd6"
+ "shas": "72f935172c31da7ddd21bf1a12c7baeb4fdb3419..1b88f5fd6eaa6af48eef0522c818919cc89fe0f3"
}
,{
"testCaseDescription": "ruby-element-reference-replacement-insert-test",
@@ -171,7 +171,7 @@
" foo[bar] = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9df6e5ca2983e03c49491c3406b07d340e9fefd6..12c1bad022b8d64c433982681853dc68e3250789"
+ "shas": "1b88f5fd6eaa6af48eef0522c818919cc89fe0f3..3114590b91f23ee9d8e9656e3c597b7710c5f08a"
}
,{
"testCaseDescription": "ruby-element-reference-delete-insert-test",
@@ -297,7 +297,7 @@
" foo[bar] = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "12c1bad022b8d64c433982681853dc68e3250789..7ee08d481de6e9b38cb14538d3b51e902842240b"
+ "shas": "3114590b91f23ee9d8e9656e3c597b7710c5f08a..470abdcd5adc26a44bbd001539d731e36d417046"
}
,{
"testCaseDescription": "ruby-element-reference-replacement-test",
@@ -423,7 +423,7 @@
" foo[bar] = 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7ee08d481de6e9b38cb14538d3b51e902842240b..566364e0660157a2c590f89604e18dd293688c24"
+ "shas": "470abdcd5adc26a44bbd001539d731e36d417046..ee5fbeec520aa431dcf290c4a7eb220d2bb2b674"
}
,{
"testCaseDescription": "ruby-element-reference-delete-replacement-test",
@@ -560,7 +560,7 @@
"+x[:\"c\"]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "566364e0660157a2c590f89604e18dd293688c24..882c8bbd008869873cf53441fc9e08357bab4b60"
+ "shas": "ee5fbeec520aa431dcf290c4a7eb220d2bb2b674..3fb44d52e9f12fd560773298d89b1721698f358a"
}
,{
"testCaseDescription": "ruby-element-reference-delete-test",
@@ -632,7 +632,7 @@
" x[:\"c\"]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "882c8bbd008869873cf53441fc9e08357bab4b60..c8771990232a77c2debd913c647f3361c996ab9f"
+ "shas": "3fb44d52e9f12fd560773298d89b1721698f358a..0207d27c72e4662c924f3f408396247dbc990739"
}
,{
"testCaseDescription": "ruby-element-reference-delete-rest-test",
@@ -686,5 +686,5 @@
"-x[:\"c\"]"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c8771990232a77c2debd913c647f3361c996ab9f..961acaef0af7db626ea7676f94065985b96bd114"
+ "shas": "0207d27c72e4662c924f3f408396247dbc990739..72e1f4912f54a936266422abbb53a9c2fc864992"
}]
diff --git a/test/corpus/diff-summaries/ruby/else.json b/test/corpus/diff-summaries/ruby/else.json
new file mode 100644
index 000000000..50b53b56c
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/else.json
@@ -0,0 +1,270 @@
+[{
+ "testCaseDescription": "ruby-else-setup-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index e69de29..d2757f9 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -0,0 +1,3 @@",
+ "+begin",
+ "+ foo()",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "4fed48f0abf8058f93dbb4c7361358c434c9bb6d..e1fa35de3fc02773c68ea68b126d5a42843cff03"
+}
+,{
+ "testCaseDescription": "ruby-else-insert-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Added an else block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index d2757f9..09f6b12 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -1,3 +1,4 @@",
+ " begin",
+ " foo()",
+ "+else",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "e1fa35de3fc02773c68ea68b126d5a42843cff03..37109135d5e8872de06650f214f53d5782718911"
+}
+,{
+ "testCaseDescription": "ruby-else-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ },
+ {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced an else block with an 'bar()' function call in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index 09f6b12..f9c269d 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -1,4 +1,5 @@",
+ " begin",
+ " foo()",
+ " else",
+ "+ bar()",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "37109135d5e8872de06650f214f53d5782718911..e9f5d111cea4eb38ef60719ace819f23d38d2c7b"
+}
+,{
+ "testCaseDescription": "ruby-else-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ },
+ {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'bar()' function call with the else block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index f9c269d..09f6b12 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -1,5 +1,4 @@",
+ " begin",
+ " foo()",
+ " else",
+ "- bar()",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "e9f5d111cea4eb38ef60719ace819f23d38d2c7b..343ff65611626b914e8d8a3e97c6159ef40e1262"
+}
+,{
+ "testCaseDescription": "ruby-else-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted an else block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index 09f6b12..d2757f9 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -1,4 +1,3 @@",
+ " begin",
+ " foo()",
+ "-else",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "343ff65611626b914e8d8a3e97c6159ef40e1262..d849d51a7355131232dbf59bd5b3d20fa660b059"
+}
+,{
+ "testCaseDescription": "ruby-else-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "else.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "else.rb"
+ ],
+ "patch": [
+ "diff --git a/else.rb b/else.rb",
+ "index d2757f9..e69de29 100644",
+ "--- a/else.rb",
+ "+++ b/else.rb",
+ "@@ -1,3 +0,0 @@",
+ "-begin",
+ "- foo()",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d849d51a7355131232dbf59bd5b3d20fa660b059..f6f1229dfdaa0bf7f5b33425764b3b4423e6e28c"
+}]
diff --git a/test/corpus/diff-summaries/ruby/elsif.json b/test/corpus/diff-summaries/ruby/elsif.json
new file mode 100644
index 000000000..42cf7a6f2
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/elsif.json
@@ -0,0 +1,246 @@
+[{
+ "testCaseDescription": "ruby-elsif-setup-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'bar' if statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index e69de29..89b5cd5 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -0,0 +1,3 @@",
+ "+if bar",
+ "+ foo()",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d571b61c3d53f568ed84cc6dad1c76cea2abe08d..adfbf640ca01c2a8140a30b71499b03d8e9602db"
+}
+,{
+ "testCaseDescription": "ruby-elsif-insert-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 4,
+ 1
+ ]
+ }
+ },
+ "summary": "Added the 'baz' elsif block in the 'bar' if statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index 89b5cd5..945e953 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -1,3 +1,4 @@",
+ " if bar",
+ " foo()",
+ "+elsif baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "adfbf640ca01c2a8140a30b71499b03d8e9602db..c56c2c77e578103675c05343baa6ac9b57de69c9"
+}
+,{
+ "testCaseDescription": "ruby-elsif-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'qoz()' function call in the 'baz' elsif block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index 945e953..8e4733f 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -1,4 +1,5 @@",
+ " if bar",
+ " foo()",
+ " elsif baz",
+ "+ qoz()",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c56c2c77e578103675c05343baa6ac9b57de69c9..9d868b4d65a258ca50a0432f32d6ce476a0ec90b"
+}
+,{
+ "testCaseDescription": "ruby-elsif-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'qoz()' function call in the 'baz' elsif block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index 8e4733f..945e953 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -1,5 +1,4 @@",
+ " if bar",
+ " foo()",
+ " elsif baz",
+ "- qoz()",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "9d868b4d65a258ca50a0432f32d6ce476a0ec90b..ae5492ab9e3097846c7c9365e1dba37799da7cf0"
+}
+,{
+ "testCaseDescription": "ruby-elsif-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 4,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the 'baz' elsif block in the 'bar' if statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index 945e953..89b5cd5 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -1,4 +1,3 @@",
+ " if bar",
+ " foo()",
+ "-elsif baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "ae5492ab9e3097846c7c9365e1dba37799da7cf0..3c79699074347065dc50d414845fc7dada45dc0e"
+}
+,{
+ "testCaseDescription": "ruby-elsif-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "elsif.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' if statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "elsif.rb"
+ ],
+ "patch": [
+ "diff --git a/elsif.rb b/elsif.rb",
+ "index 89b5cd5..e69de29 100644",
+ "--- a/elsif.rb",
+ "+++ b/elsif.rb",
+ "@@ -1,3 +0,0 @@",
+ "-if bar",
+ "- foo()",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "3c79699074347065dc50d414845fc7dada45dc0e..291c23618b5574de7402f710d7feba58b0edbcc2"
+}]
diff --git a/test/corpus/diff-summaries/ruby/ensure.json b/test/corpus/diff-summaries/ruby/ensure.json
new file mode 100644
index 000000000..e7b63e0ef
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/ensure.json
@@ -0,0 +1,270 @@
+[{
+ "testCaseDescription": "ruby-ensure-setup-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index e69de29..dbcd28c 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -0,0 +1,3 @@",
+ "+begin",
+ "+ foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "f6f1229dfdaa0bf7f5b33425764b3b4423e6e28c..b10ccba8ad4f11f74e74fe5eca3b97e5a604aff2"
+}
+,{
+ "testCaseDescription": "ruby-ensure-insert-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ }
+ },
+ "summary": "Added an ensure block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index dbcd28c..4332810 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -1,3 +1,4 @@",
+ " begin",
+ " foo",
+ "+ensure",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "b10ccba8ad4f11f74e74fe5eca3b97e5a604aff2..fa5e430655c2dcff9f8c706046b6c5a230172103"
+}
+,{
+ "testCaseDescription": "ruby-ensure-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ },
+ {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced an ensure block with an 'bar' identifier in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index 4332810..ddde828 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -1,4 +1,5 @@",
+ " begin",
+ " foo",
+ " ensure",
+ "+ bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "fa5e430655c2dcff9f8c706046b6c5a230172103..5eb9ced9edc1f64762468d4378055a3c44c7688c"
+}
+,{
+ "testCaseDescription": "ruby-ensure-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ },
+ {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'bar' identifier with the ensure block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index ddde828..4332810 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -1,5 +1,4 @@",
+ " begin",
+ " foo",
+ " ensure",
+ "- bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "5eb9ced9edc1f64762468d4378055a3c44c7688c..a8e6dd4fff6bf1580be14213e216207ed53cf059"
+}
+,{
+ "testCaseDescription": "ruby-ensure-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 3,
+ 7
+ ]
+ }
+ },
+ "summary": "Deleted an ensure block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index 4332810..dbcd28c 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -1,4 +1,3 @@",
+ " begin",
+ " foo",
+ "-ensure",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "a8e6dd4fff6bf1580be14213e216207ed53cf059..324595aac765613b219d4e80d627e6eb186cec57"
+}
+,{
+ "testCaseDescription": "ruby-ensure-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "ensure.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "ensure.rb"
+ ],
+ "patch": [
+ "diff --git a/ensure.rb b/ensure.rb",
+ "index dbcd28c..e69de29 100644",
+ "--- a/ensure.rb",
+ "+++ b/ensure.rb",
+ "@@ -1,3 +0,0 @@",
+ "-begin",
+ "- foo",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "324595aac765613b219d4e80d627e6eb186cec57..5df8bfbe172193e6124da27f457fa6fb19547593"
+}]
diff --git a/test/corpus/diff-summaries/ruby/for.json b/test/corpus/diff-summaries/ruby/for.json
index f6b396da7..47c94908b 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": "dd38551c64d4fadd792d042dcdb1cd760c8a81b5..fb1305cb9530ec4971af1fef14baa8e70954a5b1"
+ "shas": "b8e7a4d5034214328f3391e3c6001076f5bb6ec9..1e4b5ce7ca850c42c111c21fd9d8f38990fc3cbf"
}
,{
"testCaseDescription": "ruby-for-replacement-insert-test",
@@ -97,7 +97,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fb1305cb9530ec4971af1fef14baa8e70954a5b1..068a6419c9830e49077dc2e14494377615f8da78"
+ "shas": "1e4b5ce7ca850c42c111c21fd9d8f38990fc3cbf..c2e6812edb506dd8a3b9419e33f6d21c4998a1b7"
}
,{
"testCaseDescription": "ruby-for-delete-insert-test",
@@ -153,7 +153,7 @@
" f"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "068a6419c9830e49077dc2e14494377615f8da78..f4052a0a629b5f1c81b8ccc6b3fc250d87cb7b34"
+ "shas": "c2e6812edb506dd8a3b9419e33f6d21c4998a1b7..bd3974e67a2154631e5a3348a1c4d13d38277cf7"
}
,{
"testCaseDescription": "ruby-for-replacement-test",
@@ -209,7 +209,7 @@
" f"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f4052a0a629b5f1c81b8ccc6b3fc250d87cb7b34..4ef04a9ce00818dada95c4de1bb60035c041d3df"
+ "shas": "bd3974e67a2154631e5a3348a1c4d13d38277cf7..7547579e6c4c271afb05ba08271f0ed4b4b678ea"
}
,{
"testCaseDescription": "ruby-for-delete-replacement-test",
@@ -287,7 +287,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4ef04a9ce00818dada95c4de1bb60035c041d3df..d55945a1b5bf5293324756ed280f215eae5d320a"
+ "shas": "7547579e6c4c271afb05ba08271f0ed4b4b678ea..467953257426ae06a5f6026a93d2820676c903c0"
}
,{
"testCaseDescription": "ruby-for-delete-test",
@@ -330,7 +330,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d55945a1b5bf5293324756ed280f215eae5d320a..81b016a5f4991c2615d1a1f189f1029e0baffa8c"
+ "shas": "467953257426ae06a5f6026a93d2820676c903c0..1fd6b5413c62cdb0f0b1822736dfdacdbbc267a0"
}
,{
"testCaseDescription": "ruby-for-delete-rest-test",
@@ -370,5 +370,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "81b016a5f4991c2615d1a1f189f1029e0baffa8c..99365feb6db5e2496cd89fea86b04d3d155dbba8"
+ "shas": "1fd6b5413c62cdb0f0b1822736dfdacdbbc267a0..72f935172c31da7ddd21bf1a12c7baeb4fdb3419"
}]
diff --git a/test/corpus/diff-summaries/ruby/hash.json b/test/corpus/diff-summaries/ruby/hash.json
index c9aaed274..6e9682bcc 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": "d9eddd177d4e2bbaf20ed13f81e033f1702c23e1..5d8570a30f2d2e15b25fc2df1bcac7c86cf32bae"
+ "shas": "bcd6d0b339d47a3a232e595d43db61acf2bfae04..1618b6749dab1997b0e6606829f8594c205b0616"
}
,{
"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": "5d8570a30f2d2e15b25fc2df1bcac7c86cf32bae..db9487694f56632d52be7ce8a1b9f33731340f7b"
+ "shas": "1618b6749dab1997b0e6606829f8594c205b0616..06de914a4e27ab3c14240b993c16ca75ea2a9f74"
}
,{
"testCaseDescription": "ruby-hash-delete-insert-test",
@@ -214,7 +214,7 @@
" { :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "db9487694f56632d52be7ce8a1b9f33731340f7b..fd752d5909d1670207f363dfff4f31df24b47f37"
+ "shas": "06de914a4e27ab3c14240b993c16ca75ea2a9f74..9b4b4ff04981427a62802545d093e8536fe6b273"
}
,{
"testCaseDescription": "ruby-hash-replacement-test",
@@ -339,7 +339,7 @@
" { :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fd752d5909d1670207f363dfff4f31df24b47f37..298d6e908515f98a686669476acb600769e0ceef"
+ "shas": "9b4b4ff04981427a62802545d093e8536fe6b273..35db7ac0f6000c8534941e46f08790624d929444"
}
,{
"testCaseDescription": "ruby-hash-delete-replacement-test",
@@ -410,7 +410,7 @@
"+{ key1: \"changed value\", key2: 2, key3: true }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "298d6e908515f98a686669476acb600769e0ceef..98f9ac052173d1e922cd23eac21a9eceb278ba80"
+ "shas": "35db7ac0f6000c8534941e46f08790624d929444..673381f3ce87fd2d1102e55ce01a719ac28ad4b1"
}
,{
"testCaseDescription": "ruby-hash-delete-test",
@@ -449,7 +449,7 @@
" { key1: \"changed value\", key2: 2, key3: true }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "98f9ac052173d1e922cd23eac21a9eceb278ba80..a136e7c543c9c0d4a2562fa7543bd8080d991193"
+ "shas": "673381f3ce87fd2d1102e55ce01a719ac28ad4b1..cba8ccf48ee9899a1c5ad781289fe52f129f48d4"
}
,{
"testCaseDescription": "ruby-hash-delete-rest-test",
@@ -487,5 +487,5 @@
"-{ key1: \"changed value\", key2: 2, key3: true }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a136e7c543c9c0d4a2562fa7543bd8080d991193..b06f33881ef5a8d65535fc5f044cddf24ff1033a"
+ "shas": "cba8ccf48ee9899a1c5ad781289fe52f129f48d4..5b279526f66afb77b2588f5173ce44d7cc693f97"
}]
diff --git a/test/corpus/diff-summaries/ruby/if-unless-modifiers.json b/test/corpus/diff-summaries/ruby/if-unless-modifiers.json
index 3933c3bd9..3698af040 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": "b0aa009ffe6cf99d971f753dfaa18e634d15e00b..7f1d729c650d9c9a1307006006521fcefb239438"
+ "shas": "4e2fff03bd38fd80461d8cac1a09c40ca80b2390..a156c775baf7ff53bfebb34f0b044ceca96516e0"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-replacement-insert-test",
@@ -89,7 +89,7 @@
" print unless foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7f1d729c650d9c9a1307006006521fcefb239438..2bb3eec21e615b7aa256ebb31714b30c8bda5bb3"
+ "shas": "a156c775baf7ff53bfebb34f0b044ceca96516e0..935c4f046aca16b663c3b7bbf15bb4e3b89df95f"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-insert-test",
@@ -145,7 +145,7 @@
" print unless foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2bb3eec21e615b7aa256ebb31714b30c8bda5bb3..58206505f620e26f38af3f203d6d053b47dca214"
+ "shas": "935c4f046aca16b663c3b7bbf15bb4e3b89df95f..2f5c75839c978eb166b5ce29ddcb0c663222be8e"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-replacement-test",
@@ -201,7 +201,7 @@
" print unless foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "58206505f620e26f38af3f203d6d053b47dca214..2a7f3bba5ca0a222991a6e0303f49c7f2c269cbb"
+ "shas": "2f5c75839c978eb166b5ce29ddcb0c663222be8e..85ce995a212ec872107b09fd0baba8b62286c999"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-replacement-test",
@@ -272,7 +272,7 @@
"+print if foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2a7f3bba5ca0a222991a6e0303f49c7f2c269cbb..e6aadfdd8e795fbcff022c6f28138e9c8dc01a0b"
+ "shas": "85ce995a212ec872107b09fd0baba8b62286c999..38fd6b10133d898160cd44223c081010ca440b6f"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-test",
@@ -311,7 +311,7 @@
" print if foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e6aadfdd8e795fbcff022c6f28138e9c8dc01a0b..bed57b2949ef42835281e0685a259af0a0d493f7"
+ "shas": "38fd6b10133d898160cd44223c081010ca440b6f..52722842753439887074cefb1075c6a31015bc82"
}
,{
"testCaseDescription": "ruby-if-unless-modifiers-delete-rest-test",
@@ -349,5 +349,5 @@
"-print if foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "bed57b2949ef42835281e0685a259af0a0d493f7..b97d4839e17a24809828d9e91c9b126bcd4a7539"
+ "shas": "52722842753439887074cefb1075c6a31015bc82..c7d3f438c72d2ab2a09e3fa47ba1cf9b175d2a9b"
}]
diff --git a/test/corpus/diff-summaries/ruby/if.json b/test/corpus/diff-summaries/ruby/if.json
index f720ac31d..21bb283ca 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": "6682c19351cfd7077bdb5a7dc6c978bd3b3d3346..ee62612da55444599799a08f4b987a8264f69780"
+ "shas": "51729c359e350d71395532126c23bfed960f2373..eb8e4745aa2692c20519254d7b8d27b3a2c07cac"
}
,{
"testCaseDescription": "ruby-if-replacement-insert-test",
@@ -121,7 +121,7 @@
" elsif quux"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ee62612da55444599799a08f4b987a8264f69780..4e59ad7bd02cb86d8fd088473cc47e1bfec3eec8"
+ "shas": "eb8e4745aa2692c20519254d7b8d27b3a2c07cac..a0d707f1e50df11d0aa4d3407dfcf79fad65acc6"
}
,{
"testCaseDescription": "ruby-if-delete-insert-test",
@@ -153,64 +153,37 @@
}
]
},
- "summary": "Replaced the 'x' identifier with the 'foo' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 5
- ],
- "end": [
- 2,
- 1
- ]
- },
- {
- "start": [
- 2,
- 3
- ],
- "end": [
- 2,
- 6
- ]
- }
- ]
- },
- "summary": "Replaced the '\n' expression statements with the 'bar' identifier"
+ "summary": "Replaced the 'x' identifier with the 'foo' identifier in the 'foo' if statement"
},
{
"span": {
"insert": {
"start": [
- 3,
- 7
- ],
- "end": [
- 3,
- 11
- ]
- }
- },
- "summary": "Added the 'quux' identifier"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
6
]
}
},
- "summary": "Added the 'baz' identifier"
+ "summary": "Added the 'bar' identifier in the 'foo' if statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 1
+ ]
+ }
+ },
+ "summary": "Added the 'quux' elsif block in the 'foo' if statement"
},
{
"span": {
@@ -225,7 +198,7 @@
]
}
},
- "summary": "Added the 'bat' identifier"
+ "summary": "Added the 'bat' identifier in the 'foo' if statement"
},
{
"span": {
@@ -269,7 +242,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4e59ad7bd02cb86d8fd088473cc47e1bfec3eec8..63ab3ee631264cba77129593f4c4e23231704714"
+ "shas": "a0d707f1e50df11d0aa4d3407dfcf79fad65acc6..b9ef26ef27b3cf5ad0e522a145ede60f9b4f3dc2"
}
,{
"testCaseDescription": "ruby-if-replacement-test",
@@ -301,64 +274,37 @@
}
]
},
- "summary": "Replaced the 'foo' identifier with the 'x' identifier"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 2,
- 3
- ],
- "end": [
- 2,
- 6
- ]
- },
- {
- "start": [
- 1,
- 5
- ],
- "end": [
- 2,
- 1
- ]
- }
- ]
- },
- "summary": "Replaced the 'bar' identifier with the '\n' expression statements"
+ "summary": "Replaced the 'foo' identifier with the 'x' identifier in the 'x' if statement"
},
{
"span": {
"delete": {
"start": [
- 3,
- 7
- ],
- "end": [
- 3,
- 11
- ]
- }
- },
- "summary": "Deleted the 'quux' identifier"
- },
- {
- "span": {
- "delete": {
- "start": [
- 4,
+ 2,
3
],
"end": [
- 4,
+ 2,
6
]
}
},
- "summary": "Deleted the 'baz' identifier"
+ "summary": "Deleted the 'bar' identifier in the 'x' if statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the 'quux' elsif block in the 'x' if statement"
},
{
"span": {
@@ -373,7 +319,7 @@
]
}
},
- "summary": "Deleted the 'bat' identifier"
+ "summary": "Deleted the 'bat' identifier in the 'x' if statement"
},
{
"span": {
@@ -417,7 +363,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "63ab3ee631264cba77129593f4c4e23231704714..7409555c2f77c08b187eb415f7fd9cd0a5f51a60"
+ "shas": "b9ef26ef27b3cf5ad0e522a145ede60f9b4f3dc2..af72ae7656106dce11ffcbd6c2a31e9a756b0342"
}
,{
"testCaseDescription": "ruby-if-delete-replacement-test",
@@ -475,7 +421,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7409555c2f77c08b187eb415f7fd9cd0a5f51a60..7e990bc8b6f9fa0e1494a5e125d7fbf3590d7f98"
+ "shas": "af72ae7656106dce11ffcbd6c2a31e9a756b0342..2aef901d538d790e42fec0a2a6b1522d8b4fce9e"
}
,{
"testCaseDescription": "ruby-if-delete-test",
@@ -522,7 +468,7 @@
" if y then"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7e990bc8b6f9fa0e1494a5e125d7fbf3590d7f98..8869c43fdb63d64699a97f25e8f0f5fb8c4cf669"
+ "shas": "2aef901d538d790e42fec0a2a6b1522d8b4fce9e..bd1fd56e20054df058e8bc8d3e2dd0d523ecce08"
}
,{
"testCaseDescription": "ruby-if-delete-rest-test",
@@ -578,5 +524,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8869c43fdb63d64699a97f25e8f0f5fb8c4cf669..7c1f947c182cfe31103c45d2a28ea7497bf717e5"
+ "shas": "bd1fd56e20054df058e8bc8d3e2dd0d523ecce08..4fed48f0abf8058f93dbb4c7361358c434c9bb6d"
}]
diff --git a/test/corpus/diff-summaries/ruby/interpolation.json b/test/corpus/diff-summaries/ruby/interpolation.json
index 5ff97af84..fa27c2ce2 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": "25836faa95e159d9e500e475825eb259c2f575c8..03efb0495d6efac28150b2971a89553cd256899e"
+ "shas": "2505617f30ca311da1378227cbf6a13d83647b91..ba6045bb44bd3872e04f0e0c67e330b73429defa"
}
,{
"testCaseDescription": "ruby-interpolation-replacement-insert-test",
@@ -138,7 +138,7 @@
" \"foo #{bar}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "03efb0495d6efac28150b2971a89553cd256899e..b7ecbdaf44aef75271b742cc8c4b6dbda4b791c4"
+ "shas": "ba6045bb44bd3872e04f0e0c67e330b73429defa..9eab77466f1fc1d8a2ceaed51eab7b16159d2c4c"
}
,{
"testCaseDescription": "ruby-interpolation-delete-insert-test",
@@ -221,7 +221,7 @@
" :\"foo #{bar}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b7ecbdaf44aef75271b742cc8c4b6dbda4b791c4..88e437f25af8fe96a7328aecd70cfd2581700964"
+ "shas": "9eab77466f1fc1d8a2ceaed51eab7b16159d2c4c..c23529986ecc8afd8cc26b6e54dc68f203488cd0"
}
,{
"testCaseDescription": "ruby-interpolation-replacement-test",
@@ -304,7 +304,7 @@
" :\"foo #{bar}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "88e437f25af8fe96a7328aecd70cfd2581700964..7f719f222f27baee2992048c3a0c12eafc18b7ff"
+ "shas": "c23529986ecc8afd8cc26b6e54dc68f203488cd0..477f525a5dd8fecc22f1eaaa4e77419e0255d2a9"
}
,{
"testCaseDescription": "ruby-interpolation-delete-replacement-test",
@@ -424,7 +424,7 @@
"+\"bar #{foo}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7f719f222f27baee2992048c3a0c12eafc18b7ff..03b6dc162e312b6e4aabf595a0ca3e51b45c2701"
+ "shas": "477f525a5dd8fecc22f1eaaa4e77419e0255d2a9..c84f76f558cce919ec1935a75ad1b830b4511ff8"
}
,{
"testCaseDescription": "ruby-interpolation-delete-test",
@@ -480,7 +480,7 @@
" \"bar #{foo}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "03b6dc162e312b6e4aabf595a0ca3e51b45c2701..1f8bb97bc60597e8c56f2554da7618618050bab5"
+ "shas": "c84f76f558cce919ec1935a75ad1b830b4511ff8..cf1a6e3114fde76b4c1d6ad65ac4c2c10f3a2b3a"
}
,{
"testCaseDescription": "ruby-interpolation-delete-rest-test",
@@ -534,5 +534,5 @@
"-\"bar #{foo}\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "1f8bb97bc60597e8c56f2554da7618618050bab5..1e20280b6e0ca3be21fcf83476fcda56c9883d3b"
+ "shas": "cf1a6e3114fde76b4c1d6ad65ac4c2c10f3a2b3a..ef8d34476c23317120bf744df9d41b9110a04c03"
}]
diff --git a/test/corpus/diff-summaries/ruby/lambda-dash-rocket.json b/test/corpus/diff-summaries/ruby/lambda-dash-rocket.json
index 908278a14..f79d789f7 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": "64e1c2a6efab3b80763bf70d38bc599e24d3cdaf..546c82b95640e0d6b4fc0545dc196c5e4fb0e8b4"
+ "shas": "39e3abbd0e3332afc2314759fdd350cba39b8e28..39eba620219e1cc7172b218e7f7f4cc0b945515e"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-replacement-insert-test",
@@ -97,7 +97,7 @@
" 2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "546c82b95640e0d6b4fc0545dc196c5e4fb0e8b4..992688548c6811cad0f832761286e5dc377fddcd"
+ "shas": "39eba620219e1cc7172b218e7f7f4cc0b945515e..db5ebcd81ad82fbb223f7ba862191d01280823bd"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-insert-test",
@@ -154,7 +154,7 @@
" 2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "992688548c6811cad0f832761286e5dc377fddcd..01e9bc7b6414c67ba4f4b40dd46dad885d4df0d5"
+ "shas": "db5ebcd81ad82fbb223f7ba862191d01280823bd..f31ea619acedac7aafa78d4821e3359c29837a2e"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-replacement-test",
@@ -211,7 +211,7 @@
" 2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "01e9bc7b6414c67ba4f4b40dd46dad885d4df0d5..ba1dbf8b2c338adf7012467086101adced94932c"
+ "shas": "f31ea619acedac7aafa78d4821e3359c29837a2e..78558177fbe1e8a9b635366d37dca7bc63c35a89"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-replacement-test",
@@ -288,7 +288,7 @@
"+-> { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ba1dbf8b2c338adf7012467086101adced94932c..551a96b9cd347e5fe5ecdca63f7e40b41c1efa72"
+ "shas": "78558177fbe1e8a9b635366d37dca7bc63c35a89..1b5da246d2f7c8e084437f516a1e0acef8a668b5"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-test",
@@ -330,7 +330,7 @@
" -> { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "551a96b9cd347e5fe5ecdca63f7e40b41c1efa72..56839a05d2d0b07ff7500c625f4e50c066dd4f10"
+ "shas": "1b5da246d2f7c8e084437f516a1e0acef8a668b5..885c3dd4bc6b78521a51d05585cd3600901ebc5f"
}
,{
"testCaseDescription": "ruby-lambda-dash-rocket-delete-rest-test",
@@ -368,5 +368,5 @@
"--> { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "56839a05d2d0b07ff7500c625f4e50c066dd4f10..58894a271951d5eb58759bc6f7fc4592059541e3"
+ "shas": "885c3dd4bc6b78521a51d05585cd3600901ebc5f..18022ae6ebbe9a88b3eaf0cfa0654e8f8bc5dd01"
}]
diff --git a/test/corpus/diff-summaries/ruby/lambda.json b/test/corpus/diff-summaries/ruby/lambda.json
index 9e6ca6449..d7b852692 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": "58894a271951d5eb58759bc6f7fc4592059541e3..ef13060d75b3c7882c0f07648506db8fc9e7aa47"
+ "shas": "18022ae6ebbe9a88b3eaf0cfa0654e8f8bc5dd01..3056cfc87793da5967931201f46bc12dc4186bf5"
}
,{
"testCaseDescription": "ruby-lambda-replacement-insert-test",
@@ -89,7 +89,7 @@
" lambda { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ef13060d75b3c7882c0f07648506db8fc9e7aa47..f0269c156cf6aa64f15fdbc5886d04fb22f366cc"
+ "shas": "3056cfc87793da5967931201f46bc12dc4186bf5..a33da9171f4f363df081fa60a58279175ea6bbc7"
}
,{
"testCaseDescription": "ruby-lambda-delete-insert-test",
@@ -142,7 +142,7 @@
" lambda { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f0269c156cf6aa64f15fdbc5886d04fb22f366cc..6f351cb355277e54f93d81fb83334cd6ba57dc7c"
+ "shas": "a33da9171f4f363df081fa60a58279175ea6bbc7..e52658a62a6c3953d8382d0296c267b2a9a3b3dc"
}
,{
"testCaseDescription": "ruby-lambda-replacement-test",
@@ -195,7 +195,7 @@
" lambda { foo }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6f351cb355277e54f93d81fb83334cd6ba57dc7c..7ddad0f521dca5e383d15e3838ea4c754b86aeca"
+ "shas": "e52658a62a6c3953d8382d0296c267b2a9a3b3dc..522cd601966aa3e9f5fc0f033f81cbefcd706669"
}
,{
"testCaseDescription": "ruby-lambda-delete-replacement-test",
@@ -266,7 +266,7 @@
"+lambda { |x| x + 1 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7ddad0f521dca5e383d15e3838ea4c754b86aeca..cd0f6cf57ebc12bc25dabf7a40f2fa459384fcb3"
+ "shas": "522cd601966aa3e9f5fc0f033f81cbefcd706669..1f004455547e75075f1c16f62433c080571f69ae"
}
,{
"testCaseDescription": "ruby-lambda-delete-test",
@@ -305,7 +305,7 @@
" lambda { |x| x + 1 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cd0f6cf57ebc12bc25dabf7a40f2fa459384fcb3..4fcb26d46bc0eb88ccf8aa0f207dc51976c902e6"
+ "shas": "1f004455547e75075f1c16f62433c080571f69ae..fb578efc5242fd49d72fc4e06e75adf0320ef31d"
}
,{
"testCaseDescription": "ruby-lambda-delete-rest-test",
@@ -343,5 +343,5 @@
"-lambda { |x| x + 1 }"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4fcb26d46bc0eb88ccf8aa0f207dc51976c902e6..dd38551c64d4fadd792d042dcdb1cd760c8a81b5"
+ "shas": "fb578efc5242fd49d72fc4e06e75adf0320ef31d..b8e7a4d5034214328f3391e3c6001076f5bb6ec9"
}]
diff --git a/test/corpus/diff-summaries/ruby/math-assignment.json b/test/corpus/diff-summaries/ruby/math-assignment.json
index b5e2b0f17..cb60eade9 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": "5027b0f8c8dc6adc15ff46a34a91777cc5ca4d7e..3198638c1cbdaff4ecef13279cacacb089e2e273"
+ "shas": "b8a1e5f549bc1fa5a1424093d499d32fa0987cee..5438892990d5ecfa57ee99c577aa175b73ffbabe"
}
,{
"testCaseDescription": "ruby-math-assignment-replacement-insert-test",
@@ -283,7 +283,7 @@
" x *= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3198638c1cbdaff4ecef13279cacacb089e2e273..8a8a5731a361d60f4447064b99c12a6fe6792c4a"
+ "shas": "5438892990d5ecfa57ee99c577aa175b73ffbabe..f70cdf5d64b650094018ccee6d9b42009ad22fde"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-insert-test",
@@ -337,7 +337,7 @@
" x /= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8a8a5731a361d60f4447064b99c12a6fe6792c4a..0e69075a8b9379b269ec7f3f8ddafe5ffb956248"
+ "shas": "f70cdf5d64b650094018ccee6d9b42009ad22fde..e9c35072aff21a20a3e388f9cf3c172194218160"
}
,{
"testCaseDescription": "ruby-math-assignment-replacement-test",
@@ -391,7 +391,7 @@
" x /= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0e69075a8b9379b269ec7f3f8ddafe5ffb956248..7bed43e21a0d91b9941fdfac65c4ba8f4bee8817"
+ "shas": "e9c35072aff21a20a3e388f9cf3c172194218160..76a45dcf02f834864ade4b2ed1ec5fd0dd0c7f76"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-replacement-test",
@@ -533,7 +533,7 @@
" x /= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7bed43e21a0d91b9941fdfac65c4ba8f4bee8817..7c6fe23b345e8b027b47329c88eca7c9be31f00c"
+ "shas": "76a45dcf02f834864ade4b2ed1ec5fd0dd0c7f76..33f478735db5f9a23c2760a55dfc3e4acbdc46f8"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-test",
@@ -638,7 +638,7 @@
" x *= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7c6fe23b345e8b027b47329c88eca7c9be31f00c..4dfda976b3186f80b858ca98b6e4965c371ae5b6"
+ "shas": "33f478735db5f9a23c2760a55dfc3e4acbdc46f8..f81054ebeafb1e11c934903a5f5bc2341f79a500"
}
,{
"testCaseDescription": "ruby-math-assignment-delete-rest-test",
@@ -740,5 +740,5 @@
"-x **= 1"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4dfda976b3186f80b858ca98b6e4965c371ae5b6..d75e597048bd0cbd98f3281d4924a665368b14d3"
+ "shas": "f81054ebeafb1e11c934903a5f5bc2341f79a500..6564c9c8832540d910a4118a6130305613ef9772"
}]
diff --git a/test/corpus/diff-summaries/ruby/method-calls.json b/test/corpus/diff-summaries/ruby/method-calls.json
new file mode 100644
index 000000000..9e91b4746
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/method-calls.json
@@ -0,0 +1,353 @@
+[{
+ "testCaseDescription": "ruby-method-calls-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'x.foo()' method call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index e69de29..5831d31 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -0,0 +1 @@",
+ "+x.foo()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "17903b081197a8af07c0566effcb951a5c2b4e92..e934fefb49abf087c33e1240f8f6dd8750461981"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar()' function call"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'x.foo()' method call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index 5831d31..ce891a7 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1 +1,3 @@",
+ "+bar()",
+ "+x.foo()",
+ " x.foo()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "e934fefb49abf087c33e1240f8f6dd8750461981..aa456894a021e11601d5c5545633e8f9391038a9"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ },
+ "summary": "Added the 'x.foo()' method call"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar()' function call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index ce891a7..472abf1 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1,3 +1,3 @@",
+ "-bar()",
+ "+x.foo()",
+ " x.foo()",
+ " x.foo()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "aa456894a021e11601d5c5545633e8f9391038a9..526f90542e5291bf410c4f56e69c47282675bd1c"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar()' function call"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'x.foo()' method call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index 472abf1..ce891a7 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1,3 +1,3 @@",
+ "-x.foo()",
+ "+bar()",
+ " x.foo()",
+ " x.foo()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "526f90542e5291bf410c4f56e69c47282675bd1c..7c5ce020e41d5b01f7ea9f88acf3386f426e01e6"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar()' function call"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'x.foo()' method call"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar()' function call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index ce891a7..6c5bbe0 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1,3 +1,2 @@",
+ "-bar()",
+ "-x.foo()",
+ " x.foo()",
+ "+bar()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "7c5ce020e41d5b01f7ea9f88acf3386f426e01e6..ee7be1e9e40189aa48d053b3891b9f9ad093db4e"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-delete-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ },
+ "summary": "Deleted the 'x.foo()' method call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index 6c5bbe0..4be2e26 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1,2 +1 @@",
+ "-x.foo()",
+ " bar()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "ee7be1e9e40189aa48d053b3891b9f9ad093db4e..beafe8aef216cb2b54edb534e94edb3fd5138052"
+}
+,{
+ "testCaseDescription": "ruby-method-calls-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "method-calls.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar()' function call"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-calls.rb"
+ ],
+ "patch": [
+ "diff --git a/method-calls.rb b/method-calls.rb",
+ "index 4be2e26..e69de29 100644",
+ "--- a/method-calls.rb",
+ "+++ b/method-calls.rb",
+ "@@ -1 +0,0 @@",
+ "-bar()"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "beafe8aef216cb2b54edb534e94edb3fd5138052..eb51a430951de620d64e6e92df9603e953708321"
+}]
diff --git a/test/corpus/diff-summaries/ruby/method-declaration-params.json b/test/corpus/diff-summaries/ruby/method-declaration-params.json
new file mode 100644
index 000000000..af40f0ba8
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/method-declaration-params.json
@@ -0,0 +1,268 @@
+[{
+ "testCaseDescription": "ruby-method-declaration-params-setup-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index e69de29..ff7bbbe 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -0,0 +1,2 @@",
+ "+def foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "f82bf4ad6ff1fbd5a9259bd1eacc5a0f4f859641..0197e7f75970a0d4fb4ac2094b70667322cd28f7"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-params-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 9
+ ],
+ "end": [
+ 1,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier in the 'foo(a)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index ff7bbbe..47fdd58 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -1,2 +1,2 @@",
+ "-def foo",
+ "+def foo(a)",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "0197e7f75970a0d4fb4ac2094b70667322cd28f7..552d3174c07720ca6e22d4d10793d77b8cbd8272"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-params-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 12
+ ],
+ "end": [
+ 1,
+ 13
+ ]
+ }
+ },
+ "summary": "Added the 'b' identifier in the 'foo(a, b, c)' method"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 15
+ ],
+ "end": [
+ 1,
+ 16
+ ]
+ }
+ },
+ "summary": "Added the 'c' identifier in the 'foo(a, b, c)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index 47fdd58..b9f1ab5 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -1,2 +1,2 @@",
+ "-def foo(a)",
+ "+def foo(a, b, c)",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "552d3174c07720ca6e22d4d10793d77b8cbd8272..d1de60658c07241f71d613af600c1182ae93d5ee"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-params-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 12
+ ],
+ "end": [
+ 1,
+ 13
+ ]
+ }
+ },
+ "summary": "Deleted the 'b' identifier in the 'foo(a)' method"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 15
+ ],
+ "end": [
+ 1,
+ 16
+ ]
+ }
+ },
+ "summary": "Deleted the 'c' identifier in the 'foo(a)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index b9f1ab5..47fdd58 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -1,2 +1,2 @@",
+ "-def foo(a, b, c)",
+ "+def foo(a)",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d1de60658c07241f71d613af600c1182ae93d5ee..9dbfbeb8ecb62a12415834b6b4d6acb2c25248e1"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-params-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 9
+ ],
+ "end": [
+ 1,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier in the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index 47fdd58..ff7bbbe 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -1,2 +1,2 @@",
+ "-def foo(a)",
+ "+def foo",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "9dbfbeb8ecb62a12415834b6b4d6acb2c25248e1..104d7b89ddba1700c8472a8622398479e4b75428"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-params-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration-params.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration-params.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration-params.rb b/method-declaration-params.rb",
+ "index ff7bbbe..e69de29 100644",
+ "--- a/method-declaration-params.rb",
+ "+++ b/method-declaration-params.rb",
+ "@@ -1,2 +0,0 @@",
+ "-def foo",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "104d7b89ddba1700c8472a8622398479e4b75428..38847e533e9d63b067fd46b4e3bf8e4bcd68f0db"
+}]
diff --git a/test/corpus/diff-summaries/ruby/method-declaration.json b/test/corpus/diff-summaries/ruby/method-declaration.json
new file mode 100644
index 000000000..630fe1b89
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/method-declaration.json
@@ -0,0 +1,426 @@
+[{
+ "testCaseDescription": "ruby-method-declaration-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index e69de29..ff7bbbe 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -0,0 +1,2 @@",
+ "+def foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "431277d98db3b1763f33f0ad74712c0605d7f610..252774d5f106ebd96337b469288937b17174b5ef"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'bar(a)' method"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index ff7bbbe..fcc5a9b 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,2 +1,7 @@",
+ "+def bar(a)",
+ "+ baz",
+ "+end",
+ "+def foo",
+ "+end",
+ " def foo",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "252774d5f106ebd96337b469288937b17174b5ef..35a4b8fddb3dfdc3f6d554ff18bed1a54a7f555b"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'bar' identifier with the 'foo' identifier in the 'foo()' method"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 9
+ ],
+ "end": [
+ 1,
+ 10
+ ]
+ }
+ },
+ "summary": "Deleted the 'a' identifier in the 'foo()' method"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'baz' identifier in the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index fcc5a9b..a09a49a 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,5 +1,4 @@",
+ "-def bar(a)",
+ "- baz",
+ "+def foo",
+ " end",
+ " def foo",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "35a4b8fddb3dfdc3f6d554ff18bed1a54a7f555b..2ef30f177ed4748865fbf8341e8859a13a1addc1"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 5
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'foo' identifier with the 'bar' identifier in the 'bar(a)' method"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 9
+ ],
+ "end": [
+ 1,
+ 10
+ ]
+ }
+ },
+ "summary": "Added the 'a' identifier in the 'bar(a)' method"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'baz' identifier in the 'bar(a)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index a09a49a..fcc5a9b 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,4 +1,5 @@",
+ "-def foo",
+ "+def bar(a)",
+ "+ baz",
+ " end",
+ " def foo",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "2ef30f177ed4748865fbf8341e8859a13a1addc1..da07a93d19fb9f023e1e9f660ffa1838d6493b13"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar(a)' method"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo()' method"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'bar(a)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index fcc5a9b..14b3fc2 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,7 +1,5 @@",
+ "-def bar(a)",
+ "- baz",
+ "-end",
+ " def foo",
+ " end",
+ "-def foo",
+ "+def bar(a)",
+ "+ baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "da07a93d19fb9f023e1e9f660ffa1838d6493b13..1acebf2b365c8f3d9a79e60ac9fc196926633beb"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-delete-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo()' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index 14b3fc2..d90f5cf 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,5 +1,3 @@",
+ "-def foo",
+ "-end",
+ " def bar(a)",
+ " baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1acebf2b365c8f3d9a79e60ac9fc196926633beb..dc91b88e86820f5cb807a7219c5fb0b1351be372"
+}
+,{
+ "testCaseDescription": "ruby-method-declaration-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "method-declaration.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar(a)' method"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "method-declaration.rb"
+ ],
+ "patch": [
+ "diff --git a/method-declaration.rb b/method-declaration.rb",
+ "index d90f5cf..e69de29 100644",
+ "--- a/method-declaration.rb",
+ "+++ b/method-declaration.rb",
+ "@@ -1,3 +0,0 @@",
+ "-def bar(a)",
+ "- baz",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "dc91b88e86820f5cb807a7219c5fb0b1351be372..f82bf4ad6ff1fbd5a9259bd1eacc5a0f4f859641"
+}]
diff --git a/test/corpus/diff-summaries/ruby/method-invocation.json b/test/corpus/diff-summaries/ruby/method-invocation.json
index c196029fa..ae254a071 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": "0afb16ab6d08fb158b2f5029251b71719ef2406e..537a0eb05ddd9848a4ea01b3c8c081052c0c6f64"
+ "shas": "38847e533e9d63b067fd46b4e3bf8e4bcd68f0db..337912159e09103c0f9708052b84b68f93ff3543"
}
,{
"testCaseDescription": "ruby-method-invocation-replacement-insert-test",
@@ -101,7 +101,7 @@
]
}
},
- "summary": "Added the 'foo.bar()' function call"
+ "summary": "Added the 'foo.bar()' method call"
},
{
"span": {
@@ -203,7 +203,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "537a0eb05ddd9848a4ea01b3c8c081052c0c6f64..fb3a47894560bb648fbe9598510b55a9e30338f9"
+ "shas": "337912159e09103c0f9708052b84b68f93ff3543..ea127bd5909b83d6dee0fb6be0dcc5d7bc4988fd"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-insert-test",
@@ -283,7 +283,7 @@
]
}
},
- "summary": "Deleted the 'foo.bar()' function call"
+ "summary": "Deleted the 'foo.bar()' method call"
},
{
"span": {
@@ -340,7 +340,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fb3a47894560bb648fbe9598510b55a9e30338f9..e68a67938dc767ea94ca8a8a8fe1677dcc45519f"
+ "shas": "ea127bd5909b83d6dee0fb6be0dcc5d7bc4988fd..d1a8f6f9af6a5bfd0c1668a3d18dc3843c47e114"
}
,{
"testCaseDescription": "ruby-method-invocation-replacement-test",
@@ -375,7 +375,7 @@
]
}
},
- "summary": "Added the 'foo.bar()' function call"
+ "summary": "Added the 'foo.bar()' method call"
},
{
"span": {
@@ -477,7 +477,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e68a67938dc767ea94ca8a8a8fe1677dcc45519f..15507a45bdad6c19d16da12e750cce0c615aaa7d"
+ "shas": "d1a8f6f9af6a5bfd0c1668a3d18dc3843c47e114..5fe58e778dc1c9be8f575f594e744ffefeeb4fc7"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-replacement-test",
@@ -557,7 +557,7 @@
"-bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "15507a45bdad6c19d16da12e750cce0c615aaa7d..a123affa04686da51f9482c1c248b4a1d7476dd4"
+ "shas": "5fe58e778dc1c9be8f575f594e744ffefeeb4fc7..ec527d127ee949363d1abf4cb103ecfaf766c82a"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-test",
@@ -630,7 +630,7 @@
" bar 2, 3"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a123affa04686da51f9482c1c248b4a1d7476dd4..7d7b5b23059cd5434fe27993a7b2d1872cf6289a"
+ "shas": "ec527d127ee949363d1abf4cb103ecfaf766c82a..f373fd312755ca8a3de02ecce462b619ad8460dc"
}
,{
"testCaseDescription": "ruby-method-invocation-delete-rest-test",
@@ -665,7 +665,7 @@
]
}
},
- "summary": "Deleted the 'foo.bar()' function call"
+ "summary": "Deleted the 'foo.bar()' method call"
},
{
"span": {
@@ -716,5 +716,5 @@
"-bar(2, 3)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7d7b5b23059cd5434fe27993a7b2d1872cf6289a..f50f57fa7d2de425445fedef30c77220e45b7581"
+ "shas": "f373fd312755ca8a3de02ecce462b619ad8460dc..98200bee05decb871fcfdf6858ee954898880f72"
}]
diff --git a/test/corpus/diff-summaries/ruby/module.json b/test/corpus/diff-summaries/ruby/module.json
index 30612356e..040022cfb 100644
--- a/test/corpus/diff-summaries/ruby/module.json
+++ b/test/corpus/diff-summaries/ruby/module.json
@@ -11,7 +11,7 @@
1
],
"end": [
- 5,
+ 2,
4
]
}
@@ -27,18 +27,15 @@
],
"patch": [
"diff --git a/module.rb b/module.rb",
- "index e69de29..e3c87f4 100644",
+ "index e69de29..85026ed 100644",
"--- a/module.rb",
"+++ b/module.rb",
- "@@ -0,0 +1,5 @@",
+ "@@ -0,0 +1,2 @@",
"+module Foo",
- "+ class Bar",
- "+ def self.test; end",
- "+end",
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "daa964737173b38b4dd562e5d4370fe48ccba4f6..63c19693a40780bb76f951580c7423a4dc0e7213"
+ "shas": "5df8bfbe172193e6124da27f457fa6fb19547593..9e3d30cbf214e01bac2e8ced270032fc40117c33"
}
,{
"testCaseDescription": "ruby-module-replacement-insert-test",
@@ -53,22 +50,22 @@
1
],
"end": [
- 2,
+ 4,
4
]
}
},
- "summary": "Added the 'Bar::' class"
+ "summary": "Added the 'Foo' module"
},
{
"span": {
"insert": {
"start": [
- 3,
+ 5,
1
],
"end": [
- 7,
+ 6,
4
]
}
@@ -84,58 +81,41 @@
],
"patch": [
"diff --git a/module.rb b/module.rb",
- "index e3c87f4..b650e19 100644",
+ "index 85026ed..351dcd2 100644",
"--- a/module.rb",
"+++ b/module.rb",
- "@@ -1,3 +1,10 @@",
- "+class Bar::Foo",
+ "@@ -1,2 +1,8 @@",
+ " module Foo",
+ "+ def bar",
+ "+ end",
"+end",
"+module Foo",
- "+ class Bar",
- "+ def self.test; end",
"+end",
- "+end",
- " module Foo",
- " class Bar",
- " def self.test; end"
+ "+module Foo",
+ " end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "63c19693a40780bb76f951580c7423a4dc0e7213..c90b3bb5c6076c9e77f492711f82339486f8468a"
+ "shas": "9e3d30cbf214e01bac2e8ced270032fc40117c33..070a30dadbd08713621ade900398489f3d5d8d35"
}
,{
"testCaseDescription": "ruby-module-delete-insert-test",
"expectedResult": {
"changes": {
"module.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 5,
- 4
- ]
- }
- },
- "summary": "Added the 'Foo' module"
- },
{
"span": {
"delete": {
"start": [
- 1,
- 1
+ 2,
+ 3
],
"end": [
- 2,
- 4
+ 3,
+ 6
]
}
},
- "summary": "Deleted the 'Bar::' class"
+ "summary": "Deleted the 'bar()' method in the Foo module"
}
]
},
@@ -146,21 +126,19 @@
],
"patch": [
"diff --git a/module.rb b/module.rb",
- "index b650e19..88fed43 100644",
+ "index 351dcd2..5900129 100644",
"--- a/module.rb",
"+++ b/module.rb",
- "@@ -1,4 +1,7 @@",
- "-class Bar::Foo",
- "+module Foo",
- "+ class Bar",
- "+ def self.test; end",
- "+end",
+ "@@ -1,6 +1,4 @@",
+ " module Foo",
+ "- def bar",
+ "- end",
" end",
" module Foo",
- " class Bar"
+ " end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c90b3bb5c6076c9e77f492711f82339486f8468a..3116c86941696d6ca530007bc0351d7ca142245b"
+ "shas": "070a30dadbd08713621ade900398489f3d5d8d35..164b8f9d4149fc6c28f330d764d68e2529ddfe7e"
}
,{
"testCaseDescription": "ruby-module-replacement-test",
@@ -171,31 +149,16 @@
"span": {
"insert": {
"start": [
- 1,
- 1
- ],
- "end": [
2,
- 4
- ]
- }
- },
- "summary": "Added the 'Bar::' class"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 1
+ 3
],
"end": [
- 5,
- 4
+ 3,
+ 6
]
}
},
- "summary": "Deleted the 'Foo' module"
+ "summary": "Added the 'bar()' method in the Foo module"
}
]
},
@@ -206,21 +169,19 @@
],
"patch": [
"diff --git a/module.rb b/module.rb",
- "index 88fed43..b650e19 100644",
+ "index 5900129..351dcd2 100644",
"--- a/module.rb",
"+++ b/module.rb",
- "@@ -1,7 +1,4 @@",
- "-module Foo",
- "- class Bar",
- "- def self.test; end",
- "-end",
- "+class Bar::Foo",
+ "@@ -1,4 +1,6 @@",
+ " module Foo",
+ "+ def bar",
+ "+ end",
" end",
" module Foo",
- " class Bar"
+ " end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3116c86941696d6ca530007bc0351d7ca142245b..57e9ebe0f1f7c1b16fe13a08c15c71de32e5f340"
+ "shas": "164b8f9d4149fc6c28f330d764d68e2529ddfe7e..6790c446e68c1186b5bc0256bcb13ea4f8f98dbc"
}
,{
"testCaseDescription": "ruby-module-delete-replacement-test",
@@ -235,22 +196,22 @@
1
],
"end": [
- 2,
+ 4,
4
]
}
},
- "summary": "Deleted the 'Bar::' class"
+ "summary": "Deleted the 'Foo' module"
},
{
"span": {
"delete": {
"start": [
- 3,
+ 5,
1
],
"end": [
- 7,
+ 6,
4
]
}
@@ -261,16 +222,16 @@
"span": {
"insert": {
"start": [
- 6,
+ 3,
1
],
"end": [
- 7,
+ 6,
4
]
}
},
- "summary": "Added the 'Bar::' class"
+ "summary": "Added the 'Foo' module"
}
]
},
@@ -281,26 +242,23 @@
],
"patch": [
"diff --git a/module.rb b/module.rb",
- "index b650e19..409528c 100644",
+ "index 351dcd2..66871d0 100644",
"--- a/module.rb",
"+++ b/module.rb",
- "@@ -1,12 +1,7 @@",
- "-class Bar::Foo",
- "-end",
+ "@@ -1,8 +1,6 @@",
" module Foo",
- " class Bar",
- " def self.test; end",
- " end",
- " end",
- "-module Foo",
- "- class Bar",
- "- def self.test; end",
+ "- def bar",
+ "- end",
"-end",
- "+class Bar::Foo",
+ "-module Foo",
+ " end",
+ " module Foo",
+ "+ def bar",
+ "+ end",
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "57e9ebe0f1f7c1b16fe13a08c15c71de32e5f340..75f4721a8125c1a8fb8e586aa31448352a39e321"
+ "shas": "6790c446e68c1186b5bc0256bcb13ea4f8f98dbc..ec4ecafdea519cb0020ed5599ff939570d0f854b"
}
,{
"testCaseDescription": "ruby-module-delete-test",
@@ -315,7 +273,7 @@
1
],
"end": [
- 5,
+ 2,
4
]
}
@@ -331,20 +289,19 @@
],
"patch": [
"diff --git a/module.rb b/module.rb",
- "index 409528c..cecfae0 100644",
+ "index 66871d0..56f77bb 100644",
"--- a/module.rb",
"+++ b/module.rb",
- "@@ -1,7 +1,2 @@",
+ "@@ -1,6 +1,4 @@",
+ " module Foo",
+ "-end",
"-module Foo",
- "- class Bar",
- "- def self.test; end",
- "-end",
- "-end",
- " class Bar::Foo",
+ " def bar",
+ " end",
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "75f4721a8125c1a8fb8e586aa31448352a39e321..ab804a5c1e94268fd3aa41e8e9b833f0eed45331"
+ "shas": "ec4ecafdea519cb0020ed5599ff939570d0f854b..57a8fb4e465c80ab42466968a539a77bf8880f5a"
}
,{
"testCaseDescription": "ruby-module-delete-rest-test",
@@ -359,12 +316,12 @@
1
],
"end": [
- 2,
+ 4,
4
]
}
},
- "summary": "Deleted the 'Bar::' class"
+ "summary": "Deleted the 'Foo' module"
}
]
},
@@ -375,13 +332,15 @@
],
"patch": [
"diff --git a/module.rb b/module.rb",
- "index cecfae0..e69de29 100644",
+ "index 56f77bb..e69de29 100644",
"--- a/module.rb",
"+++ b/module.rb",
- "@@ -1,2 +0,0 @@",
- "-class Bar::Foo",
+ "@@ -1,4 +0,0 @@",
+ "-module Foo",
+ "- def bar",
+ "- end",
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ab804a5c1e94268fd3aa41e8e9b833f0eed45331..adb74fae7ebd2c1493d783ae7b1b876ae00a8c3a"
+ "shas": "57a8fb4e465c80ab42466968a539a77bf8880f5a..1713f7f3e2aa6a1e643842fde9382ce098c08363"
}]
diff --git a/test/corpus/diff-summaries/ruby/multiple-assignments.json b/test/corpus/diff-summaries/ruby/multiple-assignments.json
index cfcb97ac8..180a9ebe0 100644
--- a/test/corpus/diff-summaries/ruby/multiple-assignments.json
+++ b/test/corpus/diff-summaries/ruby/multiple-assignments.json
@@ -10,17 +10,35 @@
1,
1
],
+ "end": [
+ 1,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'x' identifier"
+ }
+ ]
+ },
+ "errors": {
+ "multiple-assignments.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 2
+ ],
"end": [
1,
21
]
}
},
- "summary": "Added the 'x(…, y, z, 20, 30)' function call"
+ "summary": "Added the ', y, z = 10, 20, 30' at line 1, column 2 - line 1, column 21"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"multiple-assignments.rb"
@@ -34,7 +52,7 @@
"+x, y, z = 10, 20, 30"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ae7f80931d5929403f69e872bbbb5459015f485d..bc54ecf7a9c07f9ee31a53067180aa239bbb16ba"
+ "shas": "f99339c141252271935202cb6c4b96a5076cf574..98a5ec1c60abaf1b78a8b0e337b95a0f962b25ac"
}
,{
"testCaseDescription": "ruby-multiple-assignments-replacement-insert-test",
@@ -50,11 +68,11 @@
],
"end": [
1,
- 21
+ 2
]
}
},
- "summary": "Added the 'x(…, 40)' function call"
+ "summary": "Added the 'x' identifier"
},
{
"span": {
@@ -65,15 +83,48 @@
],
"end": [
2,
+ 2
+ ]
+ }
+ },
+ "summary": "Added the 'x' identifier"
+ }
+ ]
+ },
+ "errors": {
+ "multiple-assignments.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 2
+ ],
+ "end": [
+ 1,
21
]
}
},
- "summary": "Added the 'x(…, y, z, 20, 30)' function call"
+ "summary": "Added the ', y = aVariable, 40' at line 1, column 2 - line 1, column 21"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 2
+ ],
+ "end": [
+ 2,
+ 21
+ ]
+ }
+ },
+ "summary": "Added the ', y, z = 10, 20, 30' at line 2, column 2 - line 2, column 21"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"multiple-assignments.rb"
@@ -89,28 +140,13 @@
" x, y, z = 10, 20, 30"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "bc54ecf7a9c07f9ee31a53067180aa239bbb16ba..40d2d8c5363413c7ca00245da5220a9054c9011c"
+ "shas": "98a5ec1c60abaf1b78a8b0e337b95a0f962b25ac..c48c21b17b29aa5e6bd49b027c9b43a9e8de8555"
}
,{
"testCaseDescription": "ruby-multiple-assignments-delete-insert-test",
"expectedResult": {
"changes": {
"multiple-assignments.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 4
- ],
- "end": [
- 1,
- 5
- ]
- }
- },
- "summary": "Added the 'y' identifier in the x(…, y, z, 20, 30) function call"
- },
{
"span": {
"replace": [
@@ -119,48 +155,6 @@
1,
2
],
- "end": [
- 1,
- 17
- ]
- },
- {
- "start": [
- 1,
- 7
- ],
- "end": [
- 1,
- 13
- ]
- }
- ]
- },
- "summary": "Replaced the ', y = aVariable' at line 1, column 2 - line 1, column 17 with the 'z' assignment in the x(…, y, z, 20, 30) function call"
- },
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 15
- ],
- "end": [
- 1,
- 17
- ]
- }
- },
- "summary": "Added '20' in the x(…, y, z, 20, 30) function call"
- },
- {
- "span": {
- "replace": [
- {
- "start": [
- 1,
- 19
- ],
"end": [
1,
21
@@ -169,7 +163,7 @@
{
"start": [
1,
- 19
+ 2
],
"end": [
1,
@@ -178,29 +172,11 @@
}
]
},
- "summary": "Replaced '40' with '30' in the x(…, y, z, 20, 30) function call"
+ "summary": "Replaced the ', y = aVariable, 40' at line 1, column 2 - line 1, column 21 with the ', y, z = 10, 20, 30' at line 1, column 2 - line 1, column 21"
}
]
},
- "errors": {
- "multiple-assignments.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 2
- ],
- "end": [
- 1,
- 3
- ]
- }
- },
- "summary": "Added the ',' at line 1, column 2 - line 1, column 3 in the x(…, y, z, 20, 30) function call"
- }
- ]
- }
+ "errors": {}
},
"filePaths": [
"multiple-assignments.rb"
@@ -217,7 +193,7 @@
" x, y, z = 10, 20, 30"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "40d2d8c5363413c7ca00245da5220a9054c9011c..6495c6ec1bd0b7088c168f9dcd4c56a23d0c0103"
+ "shas": "c48c21b17b29aa5e6bd49b027c9b43a9e8de8555..980e039b8ec804ddd8dbddc853077d19dbf9120a"
}
,{
"testCaseDescription": "ruby-multiple-assignments-replacement-test",
@@ -226,115 +202,34 @@
"multiple-assignments.rb": [
{
"span": {
- "insert": {
- "start": [
- 1,
- 19
- ],
- "end": [
- 1,
- 21
- ]
- }
+ "replace": [
+ {
+ "start": [
+ 1,
+ 2
+ ],
+ "end": [
+ 1,
+ 21
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 2
+ ],
+ "end": [
+ 1,
+ 21
+ ]
+ }
+ ]
},
- "summary": "Added '40' in the x(…, 40) function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 4
- ],
- "end": [
- 1,
- 5
- ]
- }
- },
- "summary": "Deleted the 'y' identifier in the x(…, 40) function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 7
- ],
- "end": [
- 1,
- 13
- ]
- }
- },
- "summary": "Deleted the 'z' assignment in the x(…, 40) function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 15
- ],
- "end": [
- 1,
- 17
- ]
- }
- },
- "summary": "Deleted '20' in the x(…, 40) function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 19
- ],
- "end": [
- 1,
- 21
- ]
- }
- },
- "summary": "Deleted '30' in the x(…, 40) function call"
+ "summary": "Replaced the ', y, z = 10, 20, 30' at line 1, column 2 - line 1, column 21 with the ', y = aVariable, 40' at line 1, column 2 - line 1, column 21"
}
]
},
- "errors": {
- "multiple-assignments.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 1,
- 2
- ],
- "end": [
- 1,
- 17
- ]
- }
- },
- "summary": "Added the ', y = aVariable' at line 1, column 2 - line 1, column 17 in the x(…, 40) function call"
- },
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 2
- ],
- "end": [
- 1,
- 3
- ]
- }
- },
- "summary": "Deleted the ',' at line 1, column 2 - line 1, column 3 in the x(…, 40) function call"
- }
- ]
- }
+ "errors": {}
},
"filePaths": [
"multiple-assignments.rb"
@@ -351,7 +246,7 @@
" x, y, z = 10, 20, 30"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6495c6ec1bd0b7088c168f9dcd4c56a23d0c0103..cc6cc8df0bcb3cf5ce51ba23c085f1dbcf5104a0"
+ "shas": "980e039b8ec804ddd8dbddc853077d19dbf9120a..859efa4bd7103d88fddb33e725029b020f6194ac"
}
,{
"testCaseDescription": "ruby-multiple-assignments-delete-replacement-test",
@@ -367,45 +262,60 @@
],
"end": [
1,
- 21
+ 2
]
}
},
- "summary": "Deleted the 'x(…, 40)' function call"
+ "summary": "Deleted the 'x' identifier"
},
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 3,
+ 2
+ ],
+ "end": [
+ 3,
+ 21
+ ]
+ },
+ {
+ "start": [
+ 2,
+ 2
+ ],
+ "end": [
+ 2,
+ 21
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the ', y, z = 10, 20, 30' at line 3, column 2 - line 3, column 21 with the ', y = aVariable, 40' at line 2, column 2 - line 2, column 21"
+ }
+ ]
+ },
+ "errors": {
+ "multiple-assignments.rb": [
{
"span": {
"delete": {
"start": [
- 2,
- 1
+ 1,
+ 2
],
"end": [
- 2,
+ 1,
21
]
}
},
- "summary": "Deleted the 'x(…, y, z, 20, 30)' function call"
- },
- {
- "span": {
- "insert": {
- "start": [
- 2,
- 1
- ],
- "end": [
- 2,
- 21
- ]
- }
- },
- "summary": "Added the 'x(…, 40)' function call"
+ "summary": "Deleted the ', y = aVariable, 40' at line 1, column 2 - line 1, column 21"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"multiple-assignments.rb"
@@ -422,7 +332,7 @@
"+x, y = aVariable, 40"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cc6cc8df0bcb3cf5ce51ba23c085f1dbcf5104a0..8f7f48b7b92739891525739d7b62bd58f98378b9"
+ "shas": "859efa4bd7103d88fddb33e725029b020f6194ac..0db7d6e491af2074c50a647bd3fde1732a13e8a1"
}
,{
"testCaseDescription": "ruby-multiple-assignments-delete-test",
@@ -436,17 +346,35 @@
1,
1
],
+ "end": [
+ 1,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'x' identifier"
+ }
+ ]
+ },
+ "errors": {
+ "multiple-assignments.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 2
+ ],
"end": [
1,
21
]
}
},
- "summary": "Deleted the 'x(…, y, z, 20, 30)' function call"
+ "summary": "Deleted the ', y, z = 10, 20, 30' at line 1, column 2 - line 1, column 21"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"multiple-assignments.rb"
@@ -461,7 +389,7 @@
" x, y = aVariable, 40"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8f7f48b7b92739891525739d7b62bd58f98378b9..4c51e92f08422ff8e3851dedda68cdd32fa3e0fa"
+ "shas": "0db7d6e491af2074c50a647bd3fde1732a13e8a1..c6eec07b5b8f35169a6c9fec9bf0ec78776a1dc7"
}
,{
"testCaseDescription": "ruby-multiple-assignments-delete-rest-test",
@@ -475,17 +403,35 @@
1,
1
],
+ "end": [
+ 1,
+ 2
+ ]
+ }
+ },
+ "summary": "Deleted the 'x' identifier"
+ }
+ ]
+ },
+ "errors": {
+ "multiple-assignments.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 2
+ ],
"end": [
1,
21
]
}
},
- "summary": "Deleted the 'x(…, 40)' function call"
+ "summary": "Deleted the ', y = aVariable, 40' at line 1, column 2 - line 1, column 21"
}
]
- },
- "errors": {}
+ }
},
"filePaths": [
"multiple-assignments.rb"
@@ -499,5 +445,5 @@
"-x, y = aVariable, 40"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4c51e92f08422ff8e3851dedda68cdd32fa3e0fa..cf8094c2727c8d78b8bde198e3e84f9aec793452"
+ "shas": "c6eec07b5b8f35169a6c9fec9bf0ec78776a1dc7..118c643eafd1e37132a89af409f899e58621d0e4"
}]
diff --git a/test/corpus/diff-summaries/ruby/number.json b/test/corpus/diff-summaries/ruby/number.json
index 10c00fbee..f0d3fbf81 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": "89de1fd8cc6322c451fec05b9e25888a290fb45b..9e2078028b39e7abdd15b47f919ddc6a9ba37929"
+ "shas": "0f08e943de503b5d714186206425966f0517ddec..c2c6dd7da94b8e4a0cd8b0acdd5e8526f05355f2"
}
,{
"testCaseDescription": "ruby-number-replacement-insert-test",
@@ -409,7 +409,7 @@
" 0d1_234"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9e2078028b39e7abdd15b47f919ddc6a9ba37929..0a89e8cd3fa5c7a345a3628e73b0310136bc4117"
+ "shas": "c2c6dd7da94b8e4a0cd8b0acdd5e8526f05355f2..d243b819564a35405d46f58255eb9d46bc9b2e99"
}
,{
"testCaseDescription": "ruby-number-delete-insert-test",
@@ -658,7 +658,7 @@
" 1_234"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0a89e8cd3fa5c7a345a3628e73b0310136bc4117..dc4e57e3cb53b17d3941150397a193f9ee8c63f4"
+ "shas": "d243b819564a35405d46f58255eb9d46bc9b2e99..62be4a00fb4fc32b3296ff1c8ffc0bb01b15379a"
}
,{
"testCaseDescription": "ruby-number-replacement-test",
@@ -907,7 +907,7 @@
" 1_234"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "dc4e57e3cb53b17d3941150397a193f9ee8c63f4..95d5b22c2b3d2f018105aeb923951c756afce459"
+ "shas": "62be4a00fb4fc32b3296ff1c8ffc0bb01b15379a..bc3466b947814264cb346aa410b9210d315be80b"
}
,{
"testCaseDescription": "ruby-number-delete-replacement-test",
@@ -1304,7 +1304,7 @@
" "
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "95d5b22c2b3d2f018105aeb923951c756afce459..900b80f334d0ea6e8da0165686c88b663565fccd"
+ "shas": "bc3466b947814264cb346aa410b9210d315be80b..e0cf7e6edc8c07a9a62b40e4d3baee6de8b7223c"
}
,{
"testCaseDescription": "ruby-number-delete-test",
@@ -1472,7 +1472,7 @@
" 0d1_235"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "900b80f334d0ea6e8da0165686c88b663565fccd..e04791fceecfd4552ca9886d5c863b1836f90752"
+ "shas": "e0cf7e6edc8c07a9a62b40e4d3baee6de8b7223c..43f4b885483cf6653fbc4344244d4908a9509e02"
}
,{
"testCaseDescription": "ruby-number-delete-rest-test",
@@ -1607,5 +1607,5 @@
"-"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e04791fceecfd4552ca9886d5c863b1836f90752..91ef3aee80e388c23e885d8352ec55b14c0a365f"
+ "shas": "43f4b885483cf6653fbc4344244d4908a9509e02..54b8896e3161e23f3cc38414d860e49c385d98ea"
}]
diff --git a/test/corpus/diff-summaries/ruby/percent-array.json b/test/corpus/diff-summaries/ruby/percent-array.json
index 1b2076a33..0dd4b128b 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": "698867032f63fc98f3b15d9fd3e752171ef9b0ca..5674de6679e4afa3a6deaa702643bad3690bae31"
+ "shas": "79b196cace027a076f4ba235171fd4f409bdaba9..60bbbb2dee1ceb124b3a5732a1f3ee63ec515497"
}
,{
"testCaseDescription": "ruby-percent-array-replacement-insert-test",
@@ -89,7 +89,7 @@
" %w(one two)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5674de6679e4afa3a6deaa702643bad3690bae31..7ecbcc2920af36d44eb0fe1b03711edbdcd878ea"
+ "shas": "60bbbb2dee1ceb124b3a5732a1f3ee63ec515497..7331cd0d8952471a92cddf2c85b3a8a3ce74846d"
}
,{
"testCaseDescription": "ruby-percent-array-delete-insert-test",
@@ -130,7 +130,7 @@
" %w(one two)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7ecbcc2920af36d44eb0fe1b03711edbdcd878ea..220e066702be587e9e7dbb4a7342a26c6c4f316e"
+ "shas": "7331cd0d8952471a92cddf2c85b3a8a3ce74846d..0a03996c67d51dc60959a36d35bb2bb781eff19b"
}
,{
"testCaseDescription": "ruby-percent-array-replacement-test",
@@ -171,7 +171,7 @@
" %w(one two)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "220e066702be587e9e7dbb4a7342a26c6c4f316e..7a4e13859072c7429c78da0dfc13739021ebd78d"
+ "shas": "0a03996c67d51dc60959a36d35bb2bb781eff19b..864617da3f66a3b16b6ab2c7c63a0a449669fc01"
}
,{
"testCaseDescription": "ruby-percent-array-delete-replacement-test",
@@ -242,7 +242,7 @@
"+%W(one #{b} three)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7a4e13859072c7429c78da0dfc13739021ebd78d..72a117163519bcecca043f73ab3ee88383d5cec5"
+ "shas": "864617da3f66a3b16b6ab2c7c63a0a449669fc01..0bee45a0f42e71f1162b4150b0647cf13a05b8f8"
}
,{
"testCaseDescription": "ruby-percent-array-delete-test",
@@ -281,7 +281,7 @@
" %W(one #{b} three)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "72a117163519bcecca043f73ab3ee88383d5cec5..8bf56a9df292291a7eda0acbcdf25043a8d7346b"
+ "shas": "0bee45a0f42e71f1162b4150b0647cf13a05b8f8..4a8ac79d914f73b9e92da2948689badc6676ca31"
}
,{
"testCaseDescription": "ruby-percent-array-delete-rest-test",
@@ -319,5 +319,5 @@
"-%W(one #{b} three)"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8bf56a9df292291a7eda0acbcdf25043a8d7346b..64e1c2a6efab3b80763bf70d38bc599e24d3cdaf"
+ "shas": "4a8ac79d914f73b9e92da2948689badc6676ca31..39e3abbd0e3332afc2314759fdd350cba39b8e28"
}]
diff --git a/test/corpus/diff-summaries/ruby/pseudo-variables.json b/test/corpus/diff-summaries/ruby/pseudo-variables.json
index 515530bfe..039711949 100644
--- a/test/corpus/diff-summaries/ruby/pseudo-variables.json
+++ b/test/corpus/diff-summaries/ruby/pseudo-variables.json
@@ -67,7 +67,7 @@
"+true"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cf8094c2727c8d78b8bde198e3e84f9aec793452..016d97436328e681d1384144498401a5eea7e926"
+ "shas": "052401261edd2497b65b3546c0220694e89a03fb..eb4638e54cfb32940ad29a5070b90e44213e351b"
}
,{
"testCaseDescription": "ruby-pseudo-variables-replacement-insert-test",
@@ -190,7 +190,7 @@
" false"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "016d97436328e681d1384144498401a5eea7e926..2325801a5bbb1f636164f3518178b05acad1a0b9"
+ "shas": "eb4638e54cfb32940ad29a5070b90e44213e351b..35f40623910a2294db51fb259e7b4af6954dcb0f"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-insert-test",
@@ -306,7 +306,7 @@
" false"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2325801a5bbb1f636164f3518178b05acad1a0b9..9d7e3199c45afae865f7be1f7fae815ebeb0560f"
+ "shas": "35f40623910a2294db51fb259e7b4af6954dcb0f..7228ef9145f92f76d1ce1f9af3111a0a9f402636"
}
,{
"testCaseDescription": "ruby-pseudo-variables-replacement-test",
@@ -422,7 +422,7 @@
" false"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9d7e3199c45afae865f7be1f7fae815ebeb0560f..9d876bae792ede12f28c65d517b343f2057ccf60"
+ "shas": "7228ef9145f92f76d1ce1f9af3111a0a9f402636..247085a3bb210f1ee85ba391c96725e7311fce20"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-replacement-test",
@@ -594,7 +594,7 @@
"+FALSE"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9d876bae792ede12f28c65d517b343f2057ccf60..125d36cc56c5f613a0f721ee87836c5a288396b3"
+ "shas": "247085a3bb210f1ee85ba391c96725e7311fce20..3c4b678a23d925ae1efdd94cb47b240c63af6ff1"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-test",
@@ -668,7 +668,7 @@
" TRUE"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "125d36cc56c5f613a0f721ee87836c5a288396b3..42ded21b0d945b12c425db637520bdab3def2e3c"
+ "shas": "3c4b678a23d925ae1efdd94cb47b240c63af6ff1..349da6fa88ae41a84f50976e21182a5d9cd7a701"
}
,{
"testCaseDescription": "ruby-pseudo-variables-delete-rest-test",
@@ -739,5 +739,5 @@
"-FALSE"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "42ded21b0d945b12c425db637520bdab3def2e3c..9bbbfdb669130a637e82cce8a4a7203d0b7b10f1"
+ "shas": "349da6fa88ae41a84f50976e21182a5d9cd7a701..f8cc3489b25f8d1857452648c25c51084dbdbdb9"
}]
diff --git a/test/corpus/diff-summaries/ruby/regex.json b/test/corpus/diff-summaries/ruby/regex.json
index 7afdeda0d..b55291eca 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": "67c2202d60f5cb8661e9fd99d9488cfc61c51656..5fd575c0dc08ea681f112238defb1c35ef8f4fec"
+ "shas": "956b136e24f76c977fefd27d5368ecd527f721ec..49cb17b4244d627bd084dab1c7248c48a3cdb7cc"
}
,{
"testCaseDescription": "ruby-regex-replacement-insert-test",
@@ -105,7 +105,7 @@
" /^(foo|bar[^_])$/i"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "5fd575c0dc08ea681f112238defb1c35ef8f4fec..09f210555f1dc46289e26c26c061b859662ef842"
+ "shas": "49cb17b4244d627bd084dab1c7248c48a3cdb7cc..a73a7605d28b1fe2b09ce87d8db7426ea6295610"
}
,{
"testCaseDescription": "ruby-regex-delete-insert-test",
@@ -174,7 +174,7 @@
" /^(foo|bar[^_])$/i"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "09f210555f1dc46289e26c26c061b859662ef842..8490afe95df5a07d999ae6165a178af3e8702137"
+ "shas": "a73a7605d28b1fe2b09ce87d8db7426ea6295610..edcc26845e0ed493216f7b8ce1235e7a37ace55d"
}
,{
"testCaseDescription": "ruby-regex-replacement-test",
@@ -243,7 +243,7 @@
" /^(foo|bar[^_])$/i"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8490afe95df5a07d999ae6165a178af3e8702137..3124a44901992faf13489baa524f88619d556d2c"
+ "shas": "edcc26845e0ed493216f7b8ce1235e7a37ace55d..46655f4fd04784ed0fd995951c5f83018cc02d97"
}
,{
"testCaseDescription": "ruby-regex-delete-replacement-test",
@@ -285,7 +285,7 @@
"-/^(foo|bar[^_])$/i"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3124a44901992faf13489baa524f88619d556d2c..e9db11fc860f7b2458e0d17a6e01bf8dc78c4476"
+ "shas": "46655f4fd04784ed0fd995951c5f83018cc02d97..dd7c07f9f3797a03b8a34fbd1efdbc98b01d2e76"
}
,{
"testCaseDescription": "ruby-regex-delete-test",
@@ -325,7 +325,7 @@
" %rc>"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e9db11fc860f7b2458e0d17a6e01bf8dc78c4476..c10200ce2d35098ddb330171ddb6e87c6989cd42"
+ "shas": "dd7c07f9f3797a03b8a34fbd1efdbc98b01d2e76..a9ee657f847f069d80fe4f52e9b1fb3bf991f26f"
}
,{
"testCaseDescription": "ruby-regex-delete-rest-test",
@@ -379,5 +379,5 @@
"-%rc>"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c10200ce2d35098ddb330171ddb6e87c6989cd42..e7484e4c64ba50c6ce9673390ee4533e86e78aaf"
+ "shas": "a9ee657f847f069d80fe4f52e9b1fb3bf991f26f..e8c4c9b4ba151237a0e88d5a650d34ee5a5a1b61"
}]
diff --git a/test/corpus/diff-summaries/ruby/relational-operator.json b/test/corpus/diff-summaries/ruby/relational-operator.json
index 5c1e0ec8d..a27cc9234 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": "cdfe07e3ce652a0ca3282e6fb45641f687c90cc9..0bba6ffb4d95d7dd1b2872244c9c31b5b34fbdac"
+ "shas": "0c8195a0d30149b84b53bc2c98687d24a787f4dd..a1f4def52826a2f5f35936ea4974cec5ea85e091"
}
,{
"testCaseDescription": "ruby-relational-operator-replacement-insert-test",
@@ -187,7 +187,7 @@
" x === y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0bba6ffb4d95d7dd1b2872244c9c31b5b34fbdac..77c774a9480278848fb13a6ac6eff069d3ce3f7a"
+ "shas": "a1f4def52826a2f5f35936ea4974cec5ea85e091..a410e8475bcc3f55ccadce1c1de878e0f23137c8"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-insert-test",
@@ -248,7 +248,7 @@
" x === y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "77c774a9480278848fb13a6ac6eff069d3ce3f7a..757c4f6c07f644472ce4d32787e205c4dd432102"
+ "shas": "a410e8475bcc3f55ccadce1c1de878e0f23137c8..863fa3c522169326664ae03b9d6fec02d4dd9eba"
}
,{
"testCaseDescription": "ruby-relational-operator-replacement-test",
@@ -309,7 +309,7 @@
" x === y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "757c4f6c07f644472ce4d32787e205c4dd432102..58da43ffe05d8e1c27ac3ffa6f5c68c1adcf5c2f"
+ "shas": "863fa3c522169326664ae03b9d6fec02d4dd9eba..d8b19e6874eeee4b5190a4ec83a8f106c9374626"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-replacement-test",
@@ -418,7 +418,7 @@
"+x =! y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "58da43ffe05d8e1c27ac3ffa6f5c68c1adcf5c2f..0ccab35bff7e3735ea5dac1dbe90fbffb726c02a"
+ "shas": "d8b19e6874eeee4b5190a4ec83a8f106c9374626..26c6f1f20d765f5c209e74a29bb714b6b7aae5b7"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-test",
@@ -491,7 +491,7 @@
" x =! y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0ccab35bff7e3735ea5dac1dbe90fbffb726c02a..ca44eeb6bfea2261001f3d3b1abce770ad988b62"
+ "shas": "26c6f1f20d765f5c209e74a29bb714b6b7aae5b7..17932b7d6a37caa52201ba5309a86f228fb81493"
}
,{
"testCaseDescription": "ruby-relational-operator-delete-rest-test",
@@ -561,5 +561,5 @@
"-x =! y"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ca44eeb6bfea2261001f3d3b1abce770ad988b62..cba823072c13adb125530eb20fdcce1c84bb71e4"
+ "shas": "17932b7d6a37caa52201ba5309a86f228fb81493..cc9a4a6fa2a1c65983250a900daf6501538b4cd8"
}]
diff --git a/test/corpus/diff-summaries/ruby/case-statement.json b/test/corpus/diff-summaries/ruby/rescue-empty.json
similarity index 52%
rename from test/corpus/diff-summaries/ruby/case-statement.json
rename to test/corpus/diff-summaries/ruby/rescue-empty.json
index e555d460a..f8de14333 100644
--- a/test/corpus/diff-summaries/ruby/case-statement.json
+++ b/test/corpus/diff-summaries/ruby/rescue-empty.json
@@ -1,8 +1,8 @@
[{
- "testCaseDescription": "ruby-case-statement-insert-test",
+ "testCaseDescription": "ruby-rescue-empty-insert-test",
"expectedResult": {
"changes": {
- "case-statement.rb": [
+ "rescue-empty.rb": [
{
"span": {
"insert": {
@@ -11,38 +11,39 @@
1
],
"end": [
- 3,
+ 4,
4
]
}
},
- "summary": "Added the 'foo' switch statement"
+ "summary": "Added a begin statement"
}
]
},
"errors": {}
},
"filePaths": [
- "case-statement.rb"
+ "rescue-empty.rb"
],
"patch": [
- "diff --git a/case-statement.rb b/case-statement.rb",
- "index e69de29..92a40ca 100644",
- "--- a/case-statement.rb",
- "+++ b/case-statement.rb",
- "@@ -0,0 +1,3 @@",
- "+case foo",
- "+when bar",
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index e69de29..5b4fe96 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -0,0 +1,4 @@",
+ "+begin",
+ "+ foo",
+ "+rescue",
"+end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f50f57fa7d2de425445fedef30c77220e45b7581..95e873431be4e491f77c229edfacba17ccf03f14"
+ "shas": "759d04410984c3b7b0c25212ef74986fba96a76f..48354aa04a6e30841aa1b0ba10f934aba9d877bb"
}
,{
- "testCaseDescription": "ruby-case-statement-replacement-insert-test",
+ "testCaseDescription": "ruby-rescue-empty-replacement-insert-test",
"expectedResult": {
"changes": {
- "case-statement.rb": [
+ "rescue-empty.rb": [
{
"span": {
"insert": {
@@ -51,12 +52,180 @@
1
],
"end": [
- 4,
+ 5,
4
]
}
},
- "summary": "Added the 'foo' switch statement"
+ "summary": "Added a begin statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 9,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-empty.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index 5b4fe96..d74e034 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,4 +1,13 @@",
+ " begin",
+ " foo",
+ " rescue",
+ "+ bar",
+ "+end",
+ "+begin",
+ "+ foo",
+ "+rescue",
+ "+end",
+ "+begin",
+ "+ foo",
+ "+rescue",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "48354aa04a6e30841aa1b0ba10f934aba9d877bb..ffef7ac3bf0c394c4b150fc38e7d84bcc0116a90"
+}
+,{
+ "testCaseDescription": "ruby-rescue-empty-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-empty.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' identifier in a rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-empty.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index d74e034..afdc934 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,7 +1,6 @@",
+ " begin",
+ " foo",
+ " rescue",
+ "- bar",
+ " end",
+ " begin",
+ " foo"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "ffef7ac3bf0c394c4b150fc38e7d84bcc0116a90..dbf6e3412604ec2bdd35156d5b9ea52e220c5464"
+}
+,{
+ "testCaseDescription": "ruby-rescue-empty-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-empty.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar' identifier in a rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-empty.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index afdc934..d74e034 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,6 +1,7 @@",
+ " begin",
+ " foo",
+ " rescue",
+ "+ bar",
+ " end",
+ " begin",
+ " foo"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "dbf6e3412604ec2bdd35156d5b9ea52e220c5464..3df29e631fd2d388ec3f1aaca908e6b1945e7481"
+}
+,{
+ "testCaseDescription": "ruby-rescue-empty-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-empty.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 9,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
},
{
"span": {
@@ -66,131 +235,49 @@
1
],
"end": [
- 7,
+ 9,
4
]
}
},
- "summary": "Added the 'foo' switch statement"
+ "summary": "Added a begin statement"
}
]
},
"errors": {}
},
"filePaths": [
- "case-statement.rb"
+ "rescue-empty.rb"
],
"patch": [
- "diff --git a/case-statement.rb b/case-statement.rb",
- "index 92a40ca..1b4c2db 100644",
- "--- a/case-statement.rb",
- "+++ b/case-statement.rb",
- "@@ -1,3 +1,10 @@",
- " case foo",
- " when bar",
- "+else",
- "+end",
- "+case foo",
- "+when bar",
- "+end",
- "+case foo",
- "+when bar",
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index d74e034..f8a72a7 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,13 +1,9 @@",
+ " begin",
+ " foo",
+ " rescue",
+ "- bar",
+ "-end",
+ "-begin",
+ "- foo",
+ "-rescue",
+ " end",
+ " begin",
+ " foo",
+ " rescue",
+ "+ bar",
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "95e873431be4e491f77c229edfacba17ccf03f14..05c438e440ea28edaedac7f2593723a51b8c7be6"
+ "shas": "3df29e631fd2d388ec3f1aaca908e6b1945e7481..70c02489eb082cc5dd59b661bae79c8df0997ea9"
}
,{
- "testCaseDescription": "ruby-case-statement-delete-insert-test",
+ "testCaseDescription": "ruby-rescue-empty-delete-test",
"expectedResult": {
"changes": {
- "case-statement.rb": [
- {
- "span": {
- "delete": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 3,
- 5
- ]
- }
- },
- "summary": "Deleted the 'else' expression statements"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "case-statement.rb"
- ],
- "patch": [
- "diff --git a/case-statement.rb b/case-statement.rb",
- "index 1b4c2db..c90d080 100644",
- "--- a/case-statement.rb",
- "+++ b/case-statement.rb",
- "@@ -1,6 +1,5 @@",
- " case foo",
- " when bar",
- "-else",
- " end",
- " case foo",
- " when bar"
- ],
- "gitDir": "test/corpus/repos/ruby",
- "shas": "05c438e440ea28edaedac7f2593723a51b8c7be6..c53041521920675802643185c637188b9dd77b17"
-}
-,{
- "testCaseDescription": "ruby-case-statement-replacement-test",
- "expectedResult": {
- "changes": {
- "case-statement.rb": [
- {
- "span": {
- "insert": {
- "start": [
- 3,
- 1
- ],
- "end": [
- 3,
- 5
- ]
- }
- },
- "summary": "Added the 'else' expression statements"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "case-statement.rb"
- ],
- "patch": [
- "diff --git a/case-statement.rb b/case-statement.rb",
- "index c90d080..1b4c2db 100644",
- "--- a/case-statement.rb",
- "+++ b/case-statement.rb",
- "@@ -1,5 +1,6 @@",
- " case foo",
- " when bar",
- "+else",
- " end",
- " case foo",
- " when bar"
- ],
- "gitDir": "test/corpus/repos/ruby",
- "shas": "c53041521920675802643185c637188b9dd77b17..df4b9759732e4e8afbb5b297e0514cf10c9363da"
-}
-,{
- "testCaseDescription": "ruby-case-statement-delete-replacement-test",
- "expectedResult": {
- "changes": {
- "case-statement.rb": [
+ "rescue-empty.rb": [
{
"span": {
"delete": {
@@ -204,148 +291,73 @@
]
}
},
- "summary": "Deleted the 'foo' switch statement"
- },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-empty.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index f8a72a7..17dffb3 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,9 +1,5 @@",
+ " begin",
+ " foo",
+ " rescue",
+ "-end",
+ "-begin",
+ "- foo",
+ "-rescue",
+ " bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "70c02489eb082cc5dd59b661bae79c8df0997ea9..7a71af57bd14a190b95e66a932a58c1f64b3983b"
+}
+,{
+ "testCaseDescription": "ruby-rescue-empty-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-empty.rb": [
{
"span": {
"delete": {
"start": [
+ 1,
+ 1
+ ],
+ "end": [
5,
- 1
- ],
- "end": [
- 7,
4
]
}
},
- "summary": "Deleted the 'foo' switch statement"
- },
- {
- "span": {
- "insert": {
- "start": [
- 4,
- 1
- ],
- "end": [
- 7,
- 4
- ]
- }
- },
- "summary": "Added the 'foo' switch statement"
+ "summary": "Deleted a begin statement"
}
]
},
"errors": {}
},
"filePaths": [
- "case-statement.rb"
+ "rescue-empty.rb"
],
"patch": [
- "diff --git a/case-statement.rb b/case-statement.rb",
- "index 1b4c2db..7ccfe26 100644",
- "--- a/case-statement.rb",
- "+++ b/case-statement.rb",
- "@@ -1,10 +1,7 @@",
- " case foo",
- " when bar",
- "-else",
- "-end",
- "-case foo",
- "-when bar",
- " end",
- " case foo",
- " when bar",
- "+else",
- " end"
- ],
- "gitDir": "test/corpus/repos/ruby",
- "shas": "df4b9759732e4e8afbb5b297e0514cf10c9363da..77252438ee0aedaa5b2f57206554fb5eb746cf14"
-}
-,{
- "testCaseDescription": "ruby-case-statement-delete-test",
- "expectedResult": {
- "changes": {
- "case-statement.rb": [
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 3,
- 4
- ]
- }
- },
- "summary": "Deleted the 'foo' switch statement"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "case-statement.rb"
- ],
- "patch": [
- "diff --git a/case-statement.rb b/case-statement.rb",
- "index 7ccfe26..9df8788 100644",
- "--- a/case-statement.rb",
- "+++ b/case-statement.rb",
- "@@ -1,7 +1,4 @@",
- " case foo",
- " when bar",
- "-end",
- "-case foo",
- "-when bar",
- " else",
- " end"
- ],
- "gitDir": "test/corpus/repos/ruby",
- "shas": "77252438ee0aedaa5b2f57206554fb5eb746cf14..d3459860b95e0e898b24e3ab4159c00e1b48d922"
-}
-,{
- "testCaseDescription": "ruby-case-statement-delete-rest-test",
- "expectedResult": {
- "changes": {
- "case-statement.rb": [
- {
- "span": {
- "delete": {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 4
- ]
- }
- },
- "summary": "Deleted the 'foo' switch statement"
- }
- ]
- },
- "errors": {}
- },
- "filePaths": [
- "case-statement.rb"
- ],
- "patch": [
- "diff --git a/case-statement.rb b/case-statement.rb",
- "index 9df8788..e69de29 100644",
- "--- a/case-statement.rb",
- "+++ b/case-statement.rb",
- "@@ -1,4 +0,0 @@",
- "-case foo",
- "-when bar",
- "-else",
+ "diff --git a/rescue-empty.rb b/rescue-empty.rb",
+ "index 17dffb3..e69de29 100644",
+ "--- a/rescue-empty.rb",
+ "+++ b/rescue-empty.rb",
+ "@@ -1,5 +0,0 @@",
+ "-begin",
+ "- foo",
+ "-rescue",
+ "- bar",
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d3459860b95e0e898b24e3ab4159c00e1b48d922..c6b6465d210afae65e64e64da1f92884d63ad7d9"
+ "shas": "7a71af57bd14a190b95e66a932a58c1f64b3983b..e805bb575511867c24e67d81ccae909f2668e660"
}]
diff --git a/test/corpus/diff-summaries/ruby/rescue-last-ex.json b/test/corpus/diff-summaries/ruby/rescue-last-ex.json
new file mode 100644
index 000000000..9cc49bdc4
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/rescue-last-ex.json
@@ -0,0 +1,363 @@
+[{
+ "testCaseDescription": "ruby-rescue-last-ex-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index e69de29..a5dbb28 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -0,0 +1,4 @@",
+ "+begin",
+ "+ foo",
+ "+rescue Error => x",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "e805bb575511867c24e67d81ccae909f2668e660..57fbaa6c0752b39141df6d2229a40d52ab46eec2"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 9,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index a5dbb28..9c0bf85 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,4 +1,13 @@",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "+ bar",
+ "+end",
+ "+begin",
+ "+ foo",
+ "+rescue Error => x",
+ "+end",
+ "+begin",
+ "+ foo",
+ "+rescue Error => x",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "57fbaa6c0752b39141df6d2229a40d52ab46eec2..1abc809f7c5f4bce8b655282c1a89c80acdb4719"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' identifier in the 'Error, x' rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index 9c0bf85..e6fe0ab 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,7 +1,6 @@",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "- bar",
+ " end",
+ " begin",
+ " foo"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1abc809f7c5f4bce8b655282c1a89c80acdb4719..4d3835c45aaafa64cf2ea5d23c0e0a7ca25f50ba"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar' identifier in the 'Error, x' rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index e6fe0ab..9c0bf85 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,6 +1,7 @@",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "+ bar",
+ " end",
+ " begin",
+ " foo"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "4d3835c45aaafa64cf2ea5d23c0e0a7ca25f50ba..1a1c77e9e42914a1ec12b746fa9bfaf045f39be6"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 6,
+ 1
+ ],
+ "end": [
+ 9,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 5,
+ 1
+ ],
+ "end": [
+ 9,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index 9c0bf85..23c7c1b 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,13 +1,9 @@",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "- bar",
+ "-end",
+ "-begin",
+ "- foo",
+ "-rescue Error => x",
+ " end",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "+ bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1a1c77e9e42914a1ec12b746fa9bfaf045f39be6..fba897776dd4e1be1f36e4a3685fcdb77e2fdd77"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-delete-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index 23c7c1b..c247b6d 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,9 +1,5 @@",
+ " begin",
+ " foo",
+ " rescue Error => x",
+ "-end",
+ "-begin",
+ "- foo",
+ "-rescue Error => x",
+ " bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "fba897776dd4e1be1f36e4a3685fcdb77e2fdd77..c605c98f25261242ec2e73cc56004de8524dea2e"
+}
+,{
+ "testCaseDescription": "ruby-rescue-last-ex-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-last-ex.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 5,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-last-ex.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-last-ex.rb b/rescue-last-ex.rb",
+ "index c247b6d..e69de29 100644",
+ "--- a/rescue-last-ex.rb",
+ "+++ b/rescue-last-ex.rb",
+ "@@ -1,5 +0,0 @@",
+ "-begin",
+ "- foo",
+ "-rescue Error => x",
+ "- bar",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c605c98f25261242ec2e73cc56004de8524dea2e..875face60282636c8ba6fbd9db4a50c6b8b38fd2"
+}]
diff --git a/test/corpus/diff-summaries/ruby/rescue-modifier.json b/test/corpus/diff-summaries/ruby/rescue-modifier.json
new file mode 100644
index 000000000..741dbd275
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/rescue-modifier.json
@@ -0,0 +1,347 @@
+[{
+ "testCaseDescription": "ruby-rescue-modifier-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index e69de29..b0cea1a 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -0,0 +1 @@",
+ "+foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "dbbf1ed8a8cafe556ea468af463f118f3ca0f4ba..ee8d8559b436b4434abf6fb62e720fd2b2e25e67"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 17
+ ]
+ }
+ },
+ "summary": "Added the 'foo' rescue modifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index b0cea1a..79b1f6a 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1 +1,3 @@",
+ "+foo rescue false",
+ "+foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "ee8d8559b436b4434abf6fb62e720fd2b2e25e67..f757d66e78f7d4e6497ce72a70017e34180e6ed7"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 17
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'foo' rescue modifier with the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index 79b1f6a..f59c8c2 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1,3 +1,3 @@",
+ "-foo rescue false",
+ "+foo rescue nil",
+ " foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "f757d66e78f7d4e6497ce72a70017e34180e6ed7..48cf3c8ae9539479ada31649b7907f45750d3587"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 17
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'foo' rescue modifier with the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index f59c8c2..79b1f6a 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1,3 +1,3 @@",
+ "-foo rescue nil",
+ "+foo rescue false",
+ " foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "48cf3c8ae9539479ada31649b7907f45750d3587..e27305bea14543e812e35efdfad8e15916b44bce"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 17
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' rescue modifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' rescue modifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 17
+ ]
+ }
+ },
+ "summary": "Added the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index 79b1f6a..509bcea 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1,3 +1,2 @@",
+ "-foo rescue false",
+ "-foo rescue nil",
+ " foo rescue nil",
+ "+foo rescue false"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "e27305bea14543e812e35efdfad8e15916b44bce..8448399194931991c532e1431d5bb57feec7e9d2"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier-delete-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index 509bcea..c36274a 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1,2 +1 @@",
+ "-foo rescue nil",
+ " foo rescue false"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "8448399194931991c532e1431d5bb57feec7e9d2..0aa3073a2d457a147b4ce034ab0576694ff7ed6d"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 17
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier.rb b/rescue-modifier.rb",
+ "index c36274a..e69de29 100644",
+ "--- a/rescue-modifier.rb",
+ "+++ b/rescue-modifier.rb",
+ "@@ -1 +0,0 @@",
+ "-foo rescue false"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "0aa3073a2d457a147b4ce034ab0576694ff7ed6d..89be77a7b4f5ee9670276a33a97a6aa3941c9cfb"
+}]
diff --git a/test/corpus/diff-summaries/ruby/rescue-modifier2.json b/test/corpus/diff-summaries/ruby/rescue-modifier2.json
new file mode 100644
index 000000000..013965be2
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/rescue-modifier2.json
@@ -0,0 +1,347 @@
+[{
+ "testCaseDescription": "ruby-rescue-modifier2-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index e69de29..b0cea1a 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -0,0 +1 @@",
+ "+foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "89be77a7b4f5ee9670276a33a97a6aa3941c9cfb..55cdbc8c69ef00db47f231d904f083eb28f50160"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-replacement-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'bar' rescue modifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index b0cea1a..595bf2e 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1 +1,3 @@",
+ "+bar rescue nil",
+ "+foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "55cdbc8c69ef00db47f231d904f083eb28f50160..198f5f3b96b3f405c1ff2081a511fac17edc7c91"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'bar' identifier with the 'foo' identifier in the 'rescue foo' modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index 595bf2e..f59c8c2 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1,3 +1,3 @@",
+ "-bar rescue nil",
+ "+foo rescue nil",
+ " foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "198f5f3b96b3f405c1ff2081a511fac17edc7c91..1e6f032a4125e945220103becbd30842264ab52e"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 4
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'foo' identifier with the 'bar' identifier in the 'rescue bar' modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index f59c8c2..595bf2e 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1,3 +1,3 @@",
+ "-foo rescue nil",
+ "+bar rescue nil",
+ " foo rescue nil",
+ " foo rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1e6f032a4125e945220103becbd30842264ab52e..a666824e8c4d5b66c6d27e6a0246b63a3042b7a0"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' rescue modifier"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' rescue modifier"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 15
+ ]
+ }
+ },
+ "summary": "Added the 'bar' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index 595bf2e..0d0f274 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1,3 +1,2 @@",
+ "-bar rescue nil",
+ "-foo rescue nil",
+ " foo rescue nil",
+ "+bar rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "a666824e8c4d5b66c6d27e6a0246b63a3042b7a0..14d5975cd55f2b7d27ce40f3491786b5644c10a6"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-delete-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index 0d0f274..f7b54a5 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1,2 +1 @@",
+ "-foo rescue nil",
+ " bar rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "14d5975cd55f2b7d27ce40f3491786b5644c10a6..0446bcdbd6fc1e4f75ecdd984d9428c2d82e4c2a"
+}
+,{
+ "testCaseDescription": "ruby-rescue-modifier2-delete-rest-test",
+ "expectedResult": {
+ "changes": {
+ "rescue-modifier2.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 15
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' rescue modifier"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue-modifier2.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue-modifier2.rb b/rescue-modifier2.rb",
+ "index f7b54a5..e69de29 100644",
+ "--- a/rescue-modifier2.rb",
+ "+++ b/rescue-modifier2.rb",
+ "@@ -1 +0,0 @@",
+ "-bar rescue nil"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "0446bcdbd6fc1e4f75ecdd984d9428c2d82e4c2a..375e457b7d8886bdbdb8b3e131a0c001d20ac41c"
+}]
diff --git a/test/corpus/diff-summaries/ruby/rescue.json b/test/corpus/diff-summaries/ruby/rescue.json
new file mode 100644
index 000000000..cea57a6b7
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/rescue.json
@@ -0,0 +1,246 @@
+[{
+ "testCaseDescription": "ruby-rescue-setup-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Added a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index e69de29..dbcd28c 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -0,0 +1,3 @@",
+ "+begin",
+ "+ foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "7d242e1a703020b3d44a44dfca02698401fd5888..c1c1d85a11ab375b2a5cecfa753ce55794695893"
+}
+,{
+ "testCaseDescription": "ruby-rescue-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 4,
+ 1
+ ]
+ }
+ },
+ "summary": "Added the 'x' rescue block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index dbcd28c..fd1f6b9 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -1,3 +1,4 @@",
+ " begin",
+ " foo",
+ "+rescue x",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c1c1d85a11ab375b2a5cecfa753ce55794695893..d2e5d09c09142af88df3e14e001d4f8b3c50400b"
+}
+,{
+ "testCaseDescription": "ruby-rescue-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'bar' identifier in the 'x' rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index fd1f6b9..e83ea4c 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -1,4 +1,5 @@",
+ " begin",
+ " foo",
+ " rescue x",
+ "+ bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d2e5d09c09142af88df3e14e001d4f8b3c50400b..29ff959d72ec67c93481eb566a450a91a5fdb5e3"
+}
+,{
+ "testCaseDescription": "ruby-rescue-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 3
+ ],
+ "end": [
+ 4,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' identifier in the 'x' rescue block"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index e83ea4c..fd1f6b9 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -1,5 +1,4 @@",
+ " begin",
+ " foo",
+ " rescue x",
+ "- bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "29ff959d72ec67c93481eb566a450a91a5fdb5e3..1e5060ad564b33df252b8ebe36db76da23c71d11"
+}
+,{
+ "testCaseDescription": "ruby-rescue-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 1
+ ],
+ "end": [
+ 4,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the 'x' rescue block in a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index fd1f6b9..dbcd28c 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -1,4 +1,3 @@",
+ " begin",
+ " foo",
+ "-rescue x",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "1e5060ad564b33df252b8ebe36db76da23c71d11..742f43f551628274941ad509b4d47a9467022038"
+}
+,{
+ "testCaseDescription": "ruby-rescue-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "rescue.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 3,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted a begin statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "rescue.rb"
+ ],
+ "patch": [
+ "diff --git a/rescue.rb b/rescue.rb",
+ "index dbcd28c..e69de29 100644",
+ "--- a/rescue.rb",
+ "+++ b/rescue.rb",
+ "@@ -1,3 +0,0 @@",
+ "-begin",
+ "- foo",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "742f43f551628274941ad509b4d47a9467022038..759d04410984c3b7b0c25212ef74986fba96a76f"
+}]
diff --git a/test/corpus/diff-summaries/ruby/return.json b/test/corpus/diff-summaries/ruby/return.json
index c416dd032..8c61d01fc 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": "adb74fae7ebd2c1493d783ae7b1b876ae00a8c3a..4f9affd8c53dbe20b88cab7abd891898c0b935a6"
+ "shas": "b9eed5bd1eb6aacf2a54e334b4297955018776a8..bea7290ff72c82de8db2a0c9ae8eae0095f9f133"
}
,{
"testCaseDescription": "ruby-return-replacement-insert-test",
@@ -89,7 +89,7 @@
" return foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4f9affd8c53dbe20b88cab7abd891898c0b935a6..6b134da06028ade799eb5ec15caa8e3c7ef8f842"
+ "shas": "bea7290ff72c82de8db2a0c9ae8eae0095f9f133..328345c3ed837afd421202db539c4e8b374e4877"
}
,{
"testCaseDescription": "ruby-return-delete-insert-test",
@@ -130,7 +130,7 @@
" return foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6b134da06028ade799eb5ec15caa8e3c7ef8f842..56683344d73c3f6c672777ee13b7735548864a40"
+ "shas": "328345c3ed837afd421202db539c4e8b374e4877..564f0138ad63d31ca573e410cd1f69143df79e04"
}
,{
"testCaseDescription": "ruby-return-replacement-test",
@@ -171,7 +171,7 @@
" return foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "56683344d73c3f6c672777ee13b7735548864a40..f0b671d407ea685e9d4eaeb94b6206ad403cf7b6"
+ "shas": "564f0138ad63d31ca573e410cd1f69143df79e04..daf6b77e4ee816ceef89bc43e56baa339ca2708f"
}
,{
"testCaseDescription": "ruby-return-delete-replacement-test",
@@ -242,7 +242,7 @@
"+return"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f0b671d407ea685e9d4eaeb94b6206ad403cf7b6..6d8761a1d375d5debe9e46f8f8af00ea0b75988f"
+ "shas": "daf6b77e4ee816ceef89bc43e56baa339ca2708f..837ad22ea13472d087a09e873830453c9e7bf89d"
}
,{
"testCaseDescription": "ruby-return-delete-test",
@@ -281,7 +281,7 @@
" return"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6d8761a1d375d5debe9e46f8f8af00ea0b75988f..b31b96f5ab601bbd6a45519fb7e098eafdb30c02"
+ "shas": "837ad22ea13472d087a09e873830453c9e7bf89d..76fdd8535cd04dcae0eef2cddafc74d3176932f6"
}
,{
"testCaseDescription": "ruby-return-delete-rest-test",
@@ -319,5 +319,5 @@
"-return"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b31b96f5ab601bbd6a45519fb7e098eafdb30c02..c03172ead5939749538d5999a4f14260524e3483"
+ "shas": "76fdd8535cd04dcae0eef2cddafc74d3176932f6..e9e47a7e8dfaea6fade11176891263b27322f29d"
}]
diff --git a/test/corpus/diff-summaries/ruby/string.json b/test/corpus/diff-summaries/ruby/string.json
index 88edcf709..81f776c97 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": "b8369fbac8f8f06cad0217c3a15eabeac5427777..11a11ab7004124672ec4c818e59e08ebb38c97f4"
+ "shas": "59e2edbe041b887605acb7a535fcceacb50d82a3..e65d8c9000cf029d28a1673f020f37eb43dfd4be"
}
,{
"testCaseDescription": "ruby-string-replacement-insert-test",
@@ -138,7 +138,7 @@
" 'foo with \"bar\"'"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "11a11ab7004124672ec4c818e59e08ebb38c97f4..a63f53dea4f14383d50a0fe84cd6877272f380b9"
+ "shas": "e65d8c9000cf029d28a1673f020f37eb43dfd4be..ce8dd8c8d416851edf4cda7e77c90f7c84706213"
}
,{
"testCaseDescription": "ruby-string-delete-insert-test",
@@ -221,7 +221,7 @@
" ''"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a63f53dea4f14383d50a0fe84cd6877272f380b9..afa7ff5e18ca2247c6a7e84158257eb4351df34f"
+ "shas": "ce8dd8c8d416851edf4cda7e77c90f7c84706213..052fa225974c071dad866d796ddde1aecf5b0b35"
}
,{
"testCaseDescription": "ruby-string-replacement-test",
@@ -304,7 +304,7 @@
" ''"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "afa7ff5e18ca2247c6a7e84158257eb4351df34f..73ff58ac285589563a17c13d9de17d955a35a887"
+ "shas": "052fa225974c071dad866d796ddde1aecf5b0b35..7fbee64365bc046de4be39070d47b51793272da8"
}
,{
"testCaseDescription": "ruby-string-delete-replacement-test",
@@ -424,7 +424,7 @@
"+\"bar with 'foo'\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "73ff58ac285589563a17c13d9de17d955a35a887..a312f2d3750c26c7c1dfa7f49b89a8fc4c1fe9d5"
+ "shas": "7fbee64365bc046de4be39070d47b51793272da8..a54602000f3a38376ca4a677e1e0fe0da4a42275"
}
,{
"testCaseDescription": "ruby-string-delete-test",
@@ -480,7 +480,7 @@
" \"bar with 'foo'\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "a312f2d3750c26c7c1dfa7f49b89a8fc4c1fe9d5..3421e64039af7552b08507b3cb4df99d1fa79025"
+ "shas": "a54602000f3a38376ca4a677e1e0fe0da4a42275..133025dbfa9e5e2089ca6bb7fce8001446d7dee3"
}
,{
"testCaseDescription": "ruby-string-delete-rest-test",
@@ -534,5 +534,5 @@
"-\"bar with 'foo'\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3421e64039af7552b08507b3cb4df99d1fa79025..25836faa95e159d9e500e475825eb259c2f575c8"
+ "shas": "133025dbfa9e5e2089ca6bb7fce8001446d7dee3..2505617f30ca311da1378227cbf6a13d83647b91"
}]
diff --git a/test/corpus/diff-summaries/ruby/subshell.json b/test/corpus/diff-summaries/ruby/subshell.json
index 7c7cca55f..051bd4a85 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": "9bbbfdb669130a637e82cce8a4a7203d0b7b10f1..4a55b28272f8c1bdcea02ae52f05e816ec5d4fe4"
+ "shas": "f8cc3489b25f8d1857452648c25c51084dbdbdb9..522071b01d711758caecf86fae864d7a5e5e190c"
}
,{
"testCaseDescription": "ruby-subshell-replacement-insert-test",
@@ -89,7 +89,7 @@
" `ls -la`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4a55b28272f8c1bdcea02ae52f05e816ec5d4fe4..09fbbd5d90b421b7aa24b63b96dcf89dd45d6d0a"
+ "shas": "522071b01d711758caecf86fae864d7a5e5e190c..8339afa687e64dabdb372ff0b27bb39f832a1d02"
}
,{
"testCaseDescription": "ruby-subshell-delete-insert-test",
@@ -142,7 +142,7 @@
" `ls -la`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "09fbbd5d90b421b7aa24b63b96dcf89dd45d6d0a..4116bf3e447f628d4ae4a04387970b809583b3f8"
+ "shas": "8339afa687e64dabdb372ff0b27bb39f832a1d02..c719966658d8f95beafc1b182efd507251268a5b"
}
,{
"testCaseDescription": "ruby-subshell-replacement-test",
@@ -195,7 +195,7 @@
" `ls -la`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4116bf3e447f628d4ae4a04387970b809583b3f8..7e6abd17d53da9f9f18cf370a779e5982d1a70af"
+ "shas": "c719966658d8f95beafc1b182efd507251268a5b..611fa19dd10019ef47b3d7477c12855fe89177f2"
}
,{
"testCaseDescription": "ruby-subshell-delete-replacement-test",
@@ -266,7 +266,7 @@
"+`git status`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "7e6abd17d53da9f9f18cf370a779e5982d1a70af..4ee8e2b372414049a3fc12314cf5da5902901ca9"
+ "shas": "611fa19dd10019ef47b3d7477c12855fe89177f2..8d03313c9be4bcd64a2a6a3c4047c5497a00686b"
}
,{
"testCaseDescription": "ruby-subshell-delete-test",
@@ -305,7 +305,7 @@
" `git status`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4ee8e2b372414049a3fc12314cf5da5902901ca9..2f64c6226c46ce898f1295fa8904453f1608e958"
+ "shas": "8d03313c9be4bcd64a2a6a3c4047c5497a00686b..1b0cba06f36513f77bdbf325e75c866ed1311775"
}
,{
"testCaseDescription": "ruby-subshell-delete-rest-test",
@@ -343,5 +343,5 @@
"-`git status`"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2f64c6226c46ce898f1295fa8904453f1608e958..d9eddd177d4e2bbaf20ed13f81e033f1702c23e1"
+ "shas": "1b0cba06f36513f77bdbf325e75c866ed1311775..bcd6d0b339d47a3a232e595d43db61acf2bfae04"
}]
diff --git a/test/corpus/diff-summaries/ruby/symbol.json b/test/corpus/diff-summaries/ruby/symbol.json
index b8eb7f4e1..937380836 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": "91ef3aee80e388c23e885d8352ec55b14c0a365f..baa8bbf35ae4a967e60f91189e014b651bf34411"
+ "shas": "54b8896e3161e23f3cc38414d860e49c385d98ea..bf0c269b25a439dde0379686ee872b8ee1131636"
}
,{
"testCaseDescription": "ruby-symbol-replacement-insert-test",
@@ -187,7 +187,7 @@
" :\"foo\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "baa8bbf35ae4a967e60f91189e014b651bf34411..3fea8ee678add777bd421df43f26027d11bf7958"
+ "shas": "bf0c269b25a439dde0379686ee872b8ee1131636..5644f2ba2009c5ec36ecf85536876ede951bcf97"
}
,{
"testCaseDescription": "ruby-symbol-delete-insert-test",
@@ -299,7 +299,7 @@
" :\"foo\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3fea8ee678add777bd421df43f26027d11bf7958..cfbaffbaf2d1d0932cc3afb3a4bab9a091293416"
+ "shas": "5644f2ba2009c5ec36ecf85536876ede951bcf97..9c21efca119534d9cfc40651a91e427ea3d84754"
}
,{
"testCaseDescription": "ruby-symbol-replacement-test",
@@ -411,7 +411,7 @@
" :\"foo\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cfbaffbaf2d1d0932cc3afb3a4bab9a091293416..d742378ab158b2e304b0394c1a7774fc54f319db"
+ "shas": "9c21efca119534d9cfc40651a91e427ea3d84754..610699faa6dc50b24bc691c72d95dd45a35d79ec"
}
,{
"testCaseDescription": "ruby-symbol-delete-replacement-test",
@@ -580,7 +580,7 @@
"+:\"bar\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "d742378ab158b2e304b0394c1a7774fc54f319db..836aa31e1896adc3efb7ef94011b8188303c4c3b"
+ "shas": "610699faa6dc50b24bc691c72d95dd45a35d79ec..7160921649a7890563e00272e08199d7d0b78bf4"
}
,{
"testCaseDescription": "ruby-symbol-delete-test",
@@ -653,7 +653,7 @@
" :\"bar\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "836aa31e1896adc3efb7ef94011b8188303c4c3b..88f9bdbb9d0b3d716cabd42db83da7fa7bdde747"
+ "shas": "7160921649a7890563e00272e08199d7d0b78bf4..5fba852ca0df591631002d4d49e810686949681b"
}
,{
"testCaseDescription": "ruby-symbol-delete-rest-test",
@@ -723,5 +723,5 @@
"-:\"bar\""
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "88f9bdbb9d0b3d716cabd42db83da7fa7bdde747..b8369fbac8f8f06cad0217c3a15eabeac5427777"
+ "shas": "5fba852ca0df591631002d4d49e810686949681b..59e2edbe041b887605acb7a535fcceacb50d82a3"
}]
diff --git a/test/corpus/diff-summaries/ruby/ternary.json b/test/corpus/diff-summaries/ruby/ternary.json
index 7a5369589..21c4a79f4 100644
--- a/test/corpus/diff-summaries/ruby/ternary.json
+++ b/test/corpus/diff-summaries/ruby/ternary.json
@@ -12,11 +12,11 @@
],
"end": [
1,
- 26
+ 20
]
}
},
- "summary": "Added the 'condition' ternary expression"
+ "summary": "Added the 'foo' ternary expression"
}
]
},
@@ -27,14 +27,14 @@
],
"patch": [
"diff --git a/ternary.rb b/ternary.rb",
- "index e69de29..698a2e2 100644",
+ "index e69de29..cc46e6d 100644",
"--- a/ternary.rb",
"+++ b/ternary.rb",
"@@ -0,0 +1 @@",
- "+condition ? case1 : case2"
+ "+foo ? case1 : case2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6436c88397ac50ad9fd8cf92b759ac75806d2f73..2a7008cf22ec4e1a78f00e9718714ed1b4fb6902"
+ "shas": "97f870df43868da61ab367aca7fcbfdf8a77aa00..e1f849d81b2f0565744fbf4f45a7cf54b924eae8"
}
,{
"testCaseDescription": "ruby-ternary-replacement-insert-test",
@@ -43,30 +43,33 @@
"ternary.rb": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 26
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ }
},
- "summary": "Replaced the 'condition' ternary expression with the 'if condition then case 1 else case2\ncondition ? case1 : case2\ncondition ? case1 : case2\n' at line 1, column 1 - line 4, column 1"
+ "summary": "Added the 'bar' ternary expression"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ }
+ },
+ "summary": "Added the 'foo' ternary expression"
}
]
},
@@ -77,16 +80,16 @@
],
"patch": [
"diff --git a/ternary.rb b/ternary.rb",
- "index 698a2e2..38cd95f 100644",
+ "index cc46e6d..44ee69e 100644",
"--- a/ternary.rb",
"+++ b/ternary.rb",
"@@ -1 +1,3 @@",
- "+if condition then case 1 else case2",
- "+condition ? case1 : case2",
- " condition ? case1 : case2"
+ "+bar ? a : b",
+ "+foo ? case1 : case2",
+ " foo ? case1 : case2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "2a7008cf22ec4e1a78f00e9718714ed1b4fb6902..8270f03e9ee880ab02a580030a6033a75161f2d8"
+ "shas": "e1f849d81b2f0565744fbf4f45a7cf54b924eae8..15476ef40fd0d4fd9c8ae6157dc6039fbc450716"
}
,{
"testCaseDescription": "ruby-ternary-delete-insert-test",
@@ -102,8 +105,8 @@
1
],
"end": [
- 4,
- 1
+ 1,
+ 4
]
},
{
@@ -113,12 +116,66 @@
],
"end": [
1,
- 26
+ 4
]
}
]
},
- "summary": "Replaced the 'if condition then case 1 else case2\ncondition ? case1 : case2\ncondition ? case1 : case2\n' at line 1, column 1 - line 4, column 1 with the 'condition' ternary expression"
+ "summary": "Replaced the 'bar' identifier with the 'foo' identifier in the 'foo' ternary expression"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'a' identifier with the 'case1' identifier in the 'foo' ternary expression"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 11
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 15
+ ],
+ "end": [
+ 1,
+ 20
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'b' identifier with the 'case2' identifier in the 'foo' ternary expression"
}
]
},
@@ -129,17 +186,17 @@
],
"patch": [
"diff --git a/ternary.rb b/ternary.rb",
- "index 38cd95f..411fded 100644",
+ "index 44ee69e..86614c8 100644",
"--- a/ternary.rb",
"+++ b/ternary.rb",
"@@ -1,3 +1,3 @@",
- "-if condition then case 1 else case2",
- "+condition ? case1 : case2",
- " condition ? case1 : case2",
- " condition ? case1 : case2"
+ "-bar ? a : b",
+ "+foo ? case1 : case2",
+ " foo ? case1 : case2",
+ " foo ? case1 : case2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8270f03e9ee880ab02a580030a6033a75161f2d8..00587528a4302fbfc5fa97f74052388e32c6efb9"
+ "shas": "15476ef40fd0d4fd9c8ae6157dc6039fbc450716..0f6207e02eb77f9f87e4a2b7256e0a80f978adc8"
}
,{
"testCaseDescription": "ruby-ternary-replacement-test",
@@ -156,7 +213,7 @@
],
"end": [
1,
- 26
+ 4
]
},
{
@@ -165,13 +222,67 @@
1
],
"end": [
- 4,
- 1
+ 1,
+ 4
]
}
]
},
- "summary": "Replaced the 'condition' ternary expression with the 'if condition then case 1 else case2\ncondition ? case1 : case2\ncondition ? case1 : case2\n' at line 1, column 1 - line 4, column 1"
+ "summary": "Replaced the 'foo' identifier with the 'bar' identifier in the 'bar' ternary expression"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 7
+ ],
+ "end": [
+ 1,
+ 8
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'case1' identifier with the 'a' identifier in the 'bar' ternary expression"
+ },
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 1,
+ 15
+ ],
+ "end": [
+ 1,
+ 20
+ ]
+ },
+ {
+ "start": [
+ 1,
+ 11
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'case2' identifier with the 'b' identifier in the 'bar' ternary expression"
}
]
},
@@ -182,17 +293,17 @@
],
"patch": [
"diff --git a/ternary.rb b/ternary.rb",
- "index 411fded..38cd95f 100644",
+ "index 86614c8..44ee69e 100644",
"--- a/ternary.rb",
"+++ b/ternary.rb",
"@@ -1,3 +1,3 @@",
- "-condition ? case1 : case2",
- "+if condition then case 1 else case2",
- " condition ? case1 : case2",
- " condition ? case1 : case2"
+ "-foo ? case1 : case2",
+ "+bar ? a : b",
+ " foo ? case1 : case2",
+ " foo ? case1 : case2"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "00587528a4302fbfc5fa97f74052388e32c6efb9..0282b16f15fb5382c393c5ade5345ded2d760226"
+ "shas": "0f6207e02eb77f9f87e4a2b7256e0a80f978adc8..1eb7b010282784002c1064e2433e57457e048cbb"
}
,{
"testCaseDescription": "ruby-ternary-delete-replacement-test",
@@ -201,30 +312,48 @@
"ternary.rb": [
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 4,
- 1
- ]
- },
- {
- "start": [
- 1,
- 1
- ],
- "end": [
- 1,
- 26
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 1,
+ 12
+ ]
+ }
},
- "summary": "Replaced the 'if condition then case 1 else case2\ncondition ? case1 : case2\ncondition ? case1 : case2\n' at line 1, column 1 - line 4, column 1 with the 'condition' ternary expression"
+ "summary": "Deleted the 'bar' ternary expression"
+ },
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 20
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' ternary expression"
+ },
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 2,
+ 12
+ ]
+ }
+ },
+ "summary": "Added the 'bar' ternary expression"
}
]
},
@@ -235,17 +364,17 @@
],
"patch": [
"diff --git a/ternary.rb b/ternary.rb",
- "index 38cd95f..32b2056 100644",
+ "index 44ee69e..1ce4e51 100644",
"--- a/ternary.rb",
"+++ b/ternary.rb",
"@@ -1,3 +1,2 @@",
- "-if condition then case 1 else case2",
- "-condition ? case1 : case2",
- " condition ? case1 : case2",
- "+if condition then case 1 else case2"
+ "-bar ? a : b",
+ "-foo ? case1 : case2",
+ " foo ? case1 : case2",
+ "+bar ? a : b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "0282b16f15fb5382c393c5ade5345ded2d760226..b82d7e261aeefd8745d87015c21b68b152a56a9d"
+ "shas": "1eb7b010282784002c1064e2433e57457e048cbb..16fba8824d7b308daeae80ae16375ff007846b9b"
}
,{
"testCaseDescription": "ruby-ternary-delete-test",
@@ -261,11 +390,11 @@
],
"end": [
1,
- 26
+ 20
]
}
},
- "summary": "Deleted the 'condition' ternary expression"
+ "summary": "Deleted the 'foo' ternary expression"
}
]
},
@@ -276,21 +405,20 @@
],
"patch": [
"diff --git a/ternary.rb b/ternary.rb",
- "index 32b2056..f53e447 100644",
+ "index 1ce4e51..7f42328 100644",
"--- a/ternary.rb",
"+++ b/ternary.rb",
"@@ -1,2 +1 @@",
- "-condition ? case1 : case2",
- " if condition then case 1 else case2"
+ "-foo ? case1 : case2",
+ " bar ? a : b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b82d7e261aeefd8745d87015c21b68b152a56a9d..205c5b1241866e1705a0f2cc080fe3da4dd5f80a"
+ "shas": "16fba8824d7b308daeae80ae16375ff007846b9b..0783eee8d94a9d7a8f7d590f0a9716617e145336"
}
,{
"testCaseDescription": "ruby-ternary-delete-rest-test",
"expectedResult": {
- "changes": {},
- "errors": {
+ "changes": {
"ternary.rb": [
{
"span": {
@@ -300,27 +428,28 @@
1
],
"end": [
- 2,
- 1
+ 1,
+ 12
]
}
},
- "summary": "Deleted the 'if condition then case 1 else case2\n' at line 1, column 1 - line 2, column 1"
+ "summary": "Deleted the 'bar' ternary expression"
}
]
- }
+ },
+ "errors": {}
},
"filePaths": [
"ternary.rb"
],
"patch": [
"diff --git a/ternary.rb b/ternary.rb",
- "index f53e447..e69de29 100644",
+ "index 7f42328..e69de29 100644",
"--- a/ternary.rb",
"+++ b/ternary.rb",
"@@ -1 +0,0 @@",
- "-if condition then case 1 else case2"
+ "-bar ? a : b"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "205c5b1241866e1705a0f2cc080fe3da4dd5f80a..0afb16ab6d08fb158b2f5029251b71719ef2406e"
+ "shas": "0783eee8d94a9d7a8f7d590f0a9716617e145336..ec2870c9e829ba9514a3fc196f778f73f25ff514"
}]
diff --git a/test/corpus/diff-summaries/ruby/unless.json b/test/corpus/diff-summaries/ruby/unless.json
index ada1413ff..5ecb0f9ca 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": "7c1f947c182cfe31103c45d2a28ea7497bf717e5..3c9d69a4042eb4b84cab2a598c910eb876a8ae59"
+ "shas": "eb51a430951de620d64e6e92df9603e953708321..3305c9604e19f1adb5acc1ac48128f02ba8824b5"
}
,{
"testCaseDescription": "ruby-unless-replacement-insert-test",
@@ -117,7 +117,7 @@
" else"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "3c9d69a4042eb4b84cab2a598c910eb876a8ae59..cd98efcd9f4096dc47e2467be6425452a824252d"
+ "shas": "3305c9604e19f1adb5acc1ac48128f02ba8824b5..b375e5596a5e365eafe9b0d2bec7778f71f80a59"
}
,{
"testCaseDescription": "ruby-unless-delete-insert-test",
@@ -149,34 +149,22 @@
}
]
},
- "summary": "Replaced the 'x' identifier with the 'foo' identifier"
+ "summary": "Replaced the 'x' identifier with the 'foo' identifier in the foo unless statement"
},
{
"span": {
- "replace": [
- {
- "start": [
- 1,
- 9
- ],
- "end": [
- 2,
- 1
- ]
- },
- {
- "start": [
- 2,
- 3
- ],
- "end": [
- 2,
- 6
- ]
- }
- ]
+ "insert": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
},
- "summary": "Replaced the '\n' expression statements with the 'bar' identifier"
+ "summary": "Added the 'bar' identifier in the foo unless statement"
},
{
"span": {
@@ -191,7 +179,7 @@
]
}
},
- "summary": "Added the 'bat' identifier"
+ "summary": "Added the 'bat' identifier in the foo unless statement"
},
{
"span": {
@@ -233,7 +221,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "cd98efcd9f4096dc47e2467be6425452a824252d..9a1353fb91d63700a0e0528c3d5ccef2954185ce"
+ "shas": "b375e5596a5e365eafe9b0d2bec7778f71f80a59..f8fdadec2dc18f26cceabd013cc59cfc925f261d"
}
,{
"testCaseDescription": "ruby-unless-replacement-test",
@@ -265,34 +253,22 @@
}
]
},
- "summary": "Replaced the 'foo' identifier with the 'x' identifier"
+ "summary": "Replaced the 'foo' identifier with the 'x' identifier in the x unless statement"
},
{
"span": {
- "replace": [
- {
- "start": [
- 2,
- 3
- ],
- "end": [
- 2,
- 6
- ]
- },
- {
- "start": [
- 1,
- 9
- ],
- "end": [
- 2,
- 1
- ]
- }
- ]
+ "delete": {
+ "start": [
+ 2,
+ 3
+ ],
+ "end": [
+ 2,
+ 6
+ ]
+ }
},
- "summary": "Replaced the 'bar' identifier with the '\n' expression statements"
+ "summary": "Deleted the 'bar' identifier in the x unless statement"
},
{
"span": {
@@ -307,7 +283,7 @@
]
}
},
- "summary": "Deleted the 'bat' identifier"
+ "summary": "Deleted the 'bat' identifier in the x unless statement"
},
{
"span": {
@@ -349,7 +325,7 @@
" bar"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "9a1353fb91d63700a0e0528c3d5ccef2954185ce..e613fb7f1b5c6cbe6b8f41f26dc806c92fcf0d77"
+ "shas": "f8fdadec2dc18f26cceabd013cc59cfc925f261d..ed0a3d5a27a0fef38499b6b79183b9afe9898a0e"
}
,{
"testCaseDescription": "ruby-unless-delete-replacement-test",
@@ -403,7 +379,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e613fb7f1b5c6cbe6b8f41f26dc806c92fcf0d77..e4263e28bfc3438ae1a48317f896cfb8e8463dc8"
+ "shas": "ed0a3d5a27a0fef38499b6b79183b9afe9898a0e..0a0941c08b3a3f65dbcbf32e375689ae3c541b42"
}
,{
"testCaseDescription": "ruby-unless-delete-test",
@@ -448,7 +424,7 @@
" unless y then"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e4263e28bfc3438ae1a48317f896cfb8e8463dc8..67401c39d445a713e51e77073aa74b43e8dc3739"
+ "shas": "0a0941c08b3a3f65dbcbf32e375689ae3c541b42..95eeab305a4bd6687a1e532bc9be0965422ba737"
}
,{
"testCaseDescription": "ruby-unless-delete-rest-test",
@@ -504,5 +480,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "67401c39d445a713e51e77073aa74b43e8dc3739..b0aa009ffe6cf99d971f753dfaa18e634d15e00b"
+ "shas": "95eeab305a4bd6687a1e532bc9be0965422ba737..4bf7d0bf7a5f56e68acbec672e139df1702a7f37"
}]
diff --git a/test/corpus/diff-summaries/ruby/until.json b/test/corpus/diff-summaries/ruby/until.json
index 9a49cd8f0..409e5be11 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": "2fc59938fe81b14014ceb37fa85f3dd5c59c2694..e5ce456ea71c2539cc31d2ef8e523bd37810a6a3"
+ "shas": "527524ae442ea64d2a0f8d057a8f3f29091b94b7..7195bbfd7970acfb3f61a3a04144c6ed735d95f8"
}
,{
"testCaseDescription": "ruby-until-replacement-insert-test",
@@ -127,7 +127,7 @@
" foo until done"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "e5ce456ea71c2539cc31d2ef8e523bd37810a6a3..fcbe6b4df04a56c2478dd0720c892a2f1e0f7eba"
+ "shas": "7195bbfd7970acfb3f61a3a04144c6ed735d95f8..a9c0d66a0ce29c04ddfdb3eeb9fd5133df7ad7c4"
}
,{
"testCaseDescription": "ruby-until-delete-insert-test",
@@ -187,7 +187,7 @@
" foo until done"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fcbe6b4df04a56c2478dd0720c892a2f1e0f7eba..19e337382e804789e76836d567a4273c67ee64fb"
+ "shas": "a9c0d66a0ce29c04ddfdb3eeb9fd5133df7ad7c4..5e66fb4320749066c271c6ee5922a6662f0f66fc"
}
,{
"testCaseDescription": "ruby-until-replacement-test",
@@ -247,7 +247,7 @@
" foo until done"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "19e337382e804789e76836d567a4273c67ee64fb..29d5e6abff85c556507873ccb22b889b55458fae"
+ "shas": "5e66fb4320749066c271c6ee5922a6662f0f66fc..aee5892096fa1235af544e9f239aea971a299847"
}
,{
"testCaseDescription": "ruby-until-delete-replacement-test",
@@ -340,7 +340,7 @@
"-foo until done"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "29d5e6abff85c556507873ccb22b889b55458fae..f5086a41b592615b3c927346c9aa9afcd8311a51"
+ "shas": "aee5892096fa1235af544e9f239aea971a299847..9fc09b78cdd42bc642860cebd38a3d5baff394b4"
}
,{
"testCaseDescription": "ruby-until-delete-test",
@@ -398,7 +398,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "f5086a41b592615b3c927346c9aa9afcd8311a51..c9c6627e41f20623558e99777479f31aeb464961"
+ "shas": "9fc09b78cdd42bc642860cebd38a3d5baff394b4..f878f5c2c585d3cab149cd4d3402426421383914"
}
,{
"testCaseDescription": "ruby-until-delete-rest-test",
@@ -438,5 +438,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c9c6627e41f20623558e99777479f31aeb464961..6682c19351cfd7077bdb5a7dc6c978bd3b3d3346"
+ "shas": "f878f5c2c585d3cab149cd4d3402426421383914..9a18b4c80b2e7e2bdca5da3ea6388d1cb4727f8f"
}]
diff --git a/test/corpus/diff-summaries/ruby/when-else.json b/test/corpus/diff-summaries/ruby/when-else.json
new file mode 100644
index 000000000..616eeee56
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/when-else.json
@@ -0,0 +1,274 @@
+[{
+ "testCaseDescription": "ruby-when-else-setup-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index e69de29..3c8eff2 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -0,0 +1,4 @@",
+ "+case foo",
+ "+when bar",
+ "+ baz",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "4bf7d0bf7a5f56e68acbec672e139df1702a7f37..5b4964a35255ff016d9da31b9cb8bf36778aa043"
+}
+,{
+ "testCaseDescription": "ruby-when-else-insert-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Added an else block in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index 3c8eff2..fb2be92 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -1,4 +1,5 @@",
+ " case foo",
+ " when bar",
+ " baz",
+ "+else",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "5b4964a35255ff016d9da31b9cb8bf36778aa043..bc90856b69058e9fbce171c0c94504ce05b21a75"
+}
+,{
+ "testCaseDescription": "ruby-when-else-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ },
+ {
+ "start": [
+ 5,
+ 3
+ ],
+ "end": [
+ 5,
+ 6
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced an else block with an 'qoz' identifier in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index fb2be92..028bb59 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -2,4 +2,5 @@ case foo",
+ " when bar",
+ " baz",
+ " else",
+ "+ qoz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "bc90856b69058e9fbce171c0c94504ce05b21a75..44f9ec6f04b1705e4fcc65bd704593c6945d7f77"
+}
+,{
+ "testCaseDescription": "ruby-when-else-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "replace": [
+ {
+ "start": [
+ 5,
+ 3
+ ],
+ "end": [
+ 5,
+ 6
+ ]
+ },
+ {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ ]
+ },
+ "summary": "Replaced the 'qoz' identifier with the else block in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index 028bb59..fb2be92 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -2,5 +2,4 @@ case foo",
+ " when bar",
+ " baz",
+ " else",
+ "- qoz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "44f9ec6f04b1705e4fcc65bd704593c6945d7f77..c1b522289f7864ca47e536478df06830c958061d"
+}
+,{
+ "testCaseDescription": "ruby-when-else-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 4,
+ 1
+ ],
+ "end": [
+ 4,
+ 5
+ ]
+ }
+ },
+ "summary": "Deleted an else block in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index fb2be92..3c8eff2 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -1,5 +1,4 @@",
+ " case foo",
+ " when bar",
+ " baz",
+ "-else",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c1b522289f7864ca47e536478df06830c958061d..c3668122d9d5da3171cf5e831a48ee3f42cdb19e"
+}
+,{
+ "testCaseDescription": "ruby-when-else-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "when-else.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 4,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when-else.rb"
+ ],
+ "patch": [
+ "diff --git a/when-else.rb b/when-else.rb",
+ "index 3c8eff2..e69de29 100644",
+ "--- a/when-else.rb",
+ "+++ b/when-else.rb",
+ "@@ -1,4 +0,0 @@",
+ "-case foo",
+ "-when bar",
+ "- baz",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c3668122d9d5da3171cf5e831a48ee3f42cdb19e..51729c359e350d71395532126c23bfed960f2373"
+}]
diff --git a/test/corpus/diff-summaries/ruby/when.json b/test/corpus/diff-summaries/ruby/when.json
new file mode 100644
index 000000000..5178efb68
--- /dev/null
+++ b/test/corpus/diff-summaries/ruby/when.json
@@ -0,0 +1,240 @@
+[{
+ "testCaseDescription": "ruby-when-setup-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Added the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index e69de29..ee23477 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -0,0 +1,2 @@",
+ "+case foo",
+ "+end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "dc9d24ac927d2ba1f4d7331d5edcf9888c6bfbdf..8584062d9a54a14c1af0ac949bf9be286269f7f7"
+}
+,{
+ "testCaseDescription": "ruby-when-insert-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 3,
+ 1
+ ]
+ }
+ },
+ "summary": "Added the 'bar' when comparison in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index ee23477..92a40ca 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -1,2 +1,3 @@",
+ " case foo",
+ "+when bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "8584062d9a54a14c1af0ac949bf9be286269f7f7..522104f5e945e8b8529bcf56c273953d72594afa"
+}
+,{
+ "testCaseDescription": "ruby-when-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "insert": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 6
+ ]
+ }
+ },
+ "summary": "Added the 'baz' identifier in a when comparison"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index 92a40ca..3c8eff2 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -1,3 +1,4 @@",
+ " case foo",
+ " when bar",
+ "+ baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "522104f5e945e8b8529bcf56c273953d72594afa..c35811be8fcc9afe2fad9fd988d9e95189c58765"
+}
+,{
+ "testCaseDescription": "ruby-when-delete-replacement-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 3,
+ 3
+ ],
+ "end": [
+ 3,
+ 6
+ ]
+ }
+ },
+ "summary": "Deleted the 'baz' identifier in a when comparison"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index 3c8eff2..92a40ca 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -1,4 +1,3 @@",
+ " case foo",
+ " when bar",
+ "- baz",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "c35811be8fcc9afe2fad9fd988d9e95189c58765..d091c742bdff6528f0464c6a0e1d369f6060ed1d"
+}
+,{
+ "testCaseDescription": "ruby-when-delete-insert-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 2,
+ 1
+ ],
+ "end": [
+ 3,
+ 1
+ ]
+ }
+ },
+ "summary": "Deleted the 'bar' when comparison in the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index 92a40ca..ee23477 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -1,3 +1,2 @@",
+ " case foo",
+ "-when bar",
+ " end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "d091c742bdff6528f0464c6a0e1d369f6060ed1d..0d554900e6183bbfd1dc9ed4b90ffb74901991d6"
+}
+,{
+ "testCaseDescription": "ruby-when-teardown-test",
+ "expectedResult": {
+ "changes": {
+ "when.rb": [
+ {
+ "span": {
+ "delete": {
+ "start": [
+ 1,
+ 1
+ ],
+ "end": [
+ 2,
+ 4
+ ]
+ }
+ },
+ "summary": "Deleted the 'foo' case statement"
+ }
+ ]
+ },
+ "errors": {}
+ },
+ "filePaths": [
+ "when.rb"
+ ],
+ "patch": [
+ "diff --git a/when.rb b/when.rb",
+ "index ee23477..e69de29 100644",
+ "--- a/when.rb",
+ "+++ b/when.rb",
+ "@@ -1,2 +0,0 @@",
+ "-case foo",
+ "-end"
+ ],
+ "gitDir": "test/corpus/repos/ruby",
+ "shas": "0d554900e6183bbfd1dc9ed4b90ffb74901991d6..c723ad6d1865bc31b8b6d554c0768635937c0ab3"
+}]
diff --git a/test/corpus/diff-summaries/ruby/while.json b/test/corpus/diff-summaries/ruby/while.json
index d528336db..8669b93ec 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": "6f68d00f29d44d034e2831ec7f508262a1afccc9..dc87d89a4628c8ce0f5e56ab41068cd8a055c359"
+ "shas": "0ea1cbaad545a54267144f11a8d792fca30cf547..1c849fa3191de04f500a9534aae7f04708bae91e"
}
,{
"testCaseDescription": "ruby-while-replacement-insert-test",
@@ -127,7 +127,7 @@
" foo while run"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "dc87d89a4628c8ce0f5e56ab41068cd8a055c359..ebd3b0611e04974d2930825fc823b72844b1d2d3"
+ "shas": "1c849fa3191de04f500a9534aae7f04708bae91e..ce45201d611ff1a381bee7c0d7b4eba2a5261228"
}
,{
"testCaseDescription": "ruby-while-delete-insert-test",
@@ -187,7 +187,7 @@
" foo while run"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ebd3b0611e04974d2930825fc823b72844b1d2d3..259d38265524f9232623d9d1bd7239c9e0270b21"
+ "shas": "ce45201d611ff1a381bee7c0d7b4eba2a5261228..76f1616d8999184e0058a66f6871ca4f039f5e1c"
}
,{
"testCaseDescription": "ruby-while-replacement-test",
@@ -247,7 +247,7 @@
" foo while run"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "259d38265524f9232623d9d1bd7239c9e0270b21..8dd4300c7f884cfbe70b009519af2c7f908c18b5"
+ "shas": "76f1616d8999184e0058a66f6871ca4f039f5e1c..d2fb5c6486f918b1d250f5561389fec71fadc005"
}
,{
"testCaseDescription": "ruby-while-delete-replacement-test",
@@ -340,7 +340,7 @@
"-foo while run"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "8dd4300c7f884cfbe70b009519af2c7f908c18b5..65626ae9f9c10ec508a5ae7c83de3caf4c5bbf26"
+ "shas": "d2fb5c6486f918b1d250f5561389fec71fadc005..deb693d7595e21ca8bf5d127aba20362b01259ee"
}
,{
"testCaseDescription": "ruby-while-delete-test",
@@ -398,7 +398,7 @@
" end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "65626ae9f9c10ec508a5ae7c83de3caf4c5bbf26..4c2e5e6a70f0a5d331413a6825f5146d2f74c48f"
+ "shas": "deb693d7595e21ca8bf5d127aba20362b01259ee..b96838d1e529db101b960f04c66dd54aeec21d92"
}
,{
"testCaseDescription": "ruby-while-delete-rest-test",
@@ -438,5 +438,5 @@
"-end"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "4c2e5e6a70f0a5d331413a6825f5146d2f74c48f..2fc59938fe81b14014ceb37fa85f3dd5c59c2694"
+ "shas": "b96838d1e529db101b960f04c66dd54aeec21d92..527524ae442ea64d2a0f8d057a8f3f29091b94b7"
}]
diff --git a/test/corpus/diff-summaries/ruby/yield.json b/test/corpus/diff-summaries/ruby/yield.json
index 8f66174d7..2fbd99c84 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": "c03172ead5939749538d5999a4f14260524e3483..fa8162bda6658937b70cec6c11cd5d92bfdf01b8"
+ "shas": "e9e47a7e8dfaea6fade11176891263b27322f29d..d3c71a8b9429b7706728aaf0e2ab22580c5a7409"
}
,{
"testCaseDescription": "ruby-yield-replacement-insert-test",
@@ -89,7 +89,7 @@
" yield foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "fa8162bda6658937b70cec6c11cd5d92bfdf01b8..6e3fe2b410b2279a03e40529e527163c63c452cf"
+ "shas": "d3c71a8b9429b7706728aaf0e2ab22580c5a7409..72ab3af267ac70da88be18c80d66436faa4d4631"
}
,{
"testCaseDescription": "ruby-yield-delete-insert-test",
@@ -130,7 +130,7 @@
" yield foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "6e3fe2b410b2279a03e40529e527163c63c452cf..ebb835c8a8293de438f8a62fc971256d851fe83c"
+ "shas": "72ab3af267ac70da88be18c80d66436faa4d4631..b4c41867bc41e284d0edc33e675ee3717fb1d913"
}
,{
"testCaseDescription": "ruby-yield-replacement-test",
@@ -171,7 +171,7 @@
" yield foo"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "ebb835c8a8293de438f8a62fc971256d851fe83c..c1b9a729c9c731f56b42ad60f12ddd9f515c15b7"
+ "shas": "b4c41867bc41e284d0edc33e675ee3717fb1d913..45587e828108c8da4b0ed81e4e9eba811537864c"
}
,{
"testCaseDescription": "ruby-yield-delete-replacement-test",
@@ -242,7 +242,7 @@
"+yield"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "c1b9a729c9c731f56b42ad60f12ddd9f515c15b7..91b18422d1033573d7b95e98f7fc141977d71b7d"
+ "shas": "45587e828108c8da4b0ed81e4e9eba811537864c..2174ca8275e9a78b58f66ad3b64a5cae11f83be0"
}
,{
"testCaseDescription": "ruby-yield-delete-test",
@@ -281,7 +281,7 @@
" yield"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "91b18422d1033573d7b95e98f7fc141977d71b7d..b60ef1dbaa2cd20f0209425e8343c6cef1184524"
+ "shas": "2174ca8275e9a78b58f66ad3b64a5cae11f83be0..ded54423d631ab67007dd284c87a8628935009ce"
}
,{
"testCaseDescription": "ruby-yield-delete-rest-test",
@@ -319,5 +319,5 @@
"-yield"
],
"gitDir": "test/corpus/repos/ruby",
- "shas": "b60ef1dbaa2cd20f0209425e8343c6cef1184524..6f68d00f29d44d034e2831ec7f508262a1afccc9"
+ "shas": "ded54423d631ab67007dd284c87a8628935009ce..0ea1cbaad545a54267144f11a8d792fca30cf547"
}]
diff --git a/test/corpus/generated/new_ruby.json b/test/corpus/generated/new_ruby.json
new file mode 100644
index 000000000..9305a903c
--- /dev/null
+++ b/test/corpus/generated/new_ruby.json
@@ -0,0 +1,14 @@
+[
+ {
+ "language": "ruby",
+ "fileExt": ".rb",
+ "repoUrl": "https://github.com/diff-fixtures/ruby.git",
+ "syntaxes": [
+ {
+ "syntax": "module",
+ "insert": "module Foo\nend",
+ "replacement": "module Foo\n def bar\n end\nend"
+ }
+ ]
+ }
+]
diff --git a/test/corpus/generated/ruby.json b/test/corpus/generated/ruby.json
index 354e14483..a908d02a4 100644
--- a/test/corpus/generated/ruby.json
+++ b/test/corpus/generated/ruby.json
@@ -91,8 +91,19 @@
},
{
"syntax": "ternary",
- "insert": "condition ? case1 : case2",
- "replacement": "if condition then case 1 else case2"
+ "insert": "foo ? case1 : case2",
+ "replacement": "bar ? a : b"
+ },
+ {
+ "syntax": "method-declaration",
+ "insert": "def foo\nend",
+ "replacement": "def bar(a)\n baz\nend"
+ },
+ {
+ "syntax": "method-declaration-params",
+ "template": "def foo{0}\nend",
+ "insert": "(a)",
+ "replacement": "(a, b, c)"
},
{
"syntax": "method-invocation",
@@ -100,9 +111,9 @@
"replacement": "print(\"hello world\")\nfoo.bar()\nbar 2, 3\nbar(2, 3)"
},
{
- "syntax": "case-statement",
- "insert": "case foo\nwhen bar\nend",
- "replacement": "case foo\nwhen bar\nelse\nend"
+ "syntax": "method-calls",
+ "insert": "x.foo()",
+ "replacement": "bar()"
},
{
"syntax": "class",
@@ -111,8 +122,8 @@
},
{
"syntax": "module",
- "insert": "module Foo\n class Bar\n def self.test; end\nend\nend",
- "replacement": "class Bar::Foo\nend"
+ "insert": "module Foo\nend",
+ "replacement": "module Foo\n def bar\n end\nend"
},
{
"syntax": "return",
@@ -188,6 +199,68 @@
"syntax": "element-reference",
"insert": "foo[bar]\nfoo[:bar]\nfoo[bar] = 1",
"replacement": "x[\"b\"]\nx[:\"c\"]"
+ },
+ {
+ "syntax": "begin",
+ "template": "def foo\n{0}end",
+ "insert": "begin\nend\n",
+ "replacement": "begin\n puts 'hi'\nend\n"
+ },
+ {
+ "syntax": "else",
+ "template": "begin\n foo()\n{0}end",
+ "insert": "else\n",
+ "replacement": "else\n bar()\n"
+ },
+ {
+ "syntax": "elsif",
+ "template": "if bar\n foo()\n{0}end",
+ "insert": "elsif baz\n",
+ "replacement": "elsif baz\n qoz()\n"
+ },
+ {
+ "syntax": "ensure",
+ "template": "begin\n foo\n{0}end",
+ "insert": "ensure\n",
+ "replacement": "ensure\n bar\n"
+ },
+ {
+ "syntax": "rescue",
+ "template": "begin\n foo\n{0}end",
+ "insert": "rescue x\n",
+ "replacement": "rescue x\n bar\n"
+ },
+ {
+ "syntax": "rescue-empty",
+ "insert": "begin\n foo\nrescue\nend",
+ "replacement": "begin\n foo\nrescue\n bar\nend"
+ },
+ {
+ "syntax": "rescue-last-ex",
+ "insert": "begin\n foo\nrescue Error => x\nend",
+ "replacement": "begin\n foo\nrescue Error => x\n bar\nend"
+ },
+ {
+ "syntax": "rescue-modifier",
+ "insert": "foo rescue nil",
+ "replacement": "foo rescue false"
+ },
+ {
+ "syntax": "rescue-modifier2",
+ "insert": "foo rescue nil",
+ "replacement": "bar rescue nil"
+ },
+ {
+ "syntax": "when",
+ "template": "case foo\n{0}end",
+ "insert": "when bar\n",
+ "replacement": "when bar\n baz\n"
+ },
+ {
+ "syntax": "when-else",
+ "template": "case foo\nwhen bar\n baz\n{0}end",
+ "insert": "else\n",
+ "replacement": "else\n qoz\n"
}
]
}
diff --git a/test/corpus/repos/ruby b/test/corpus/repos/ruby
index 961acaef0..1713f7f3e 160000
--- a/test/corpus/repos/ruby
+++ b/test/corpus/repos/ruby
@@ -1 +1 @@
-Subproject commit 961acaef0af7db626ea7676f94065985b96bd114
+Subproject commit 1713f7f3e2aa6a1e643842fde9382ce098c08363
diff --git a/vendor/tree-sitter-parsers b/vendor/tree-sitter-parsers
index cd7e07714..4956958f4 160000
--- a/vendor/tree-sitter-parsers
+++ b/vendor/tree-sitter-parsers
@@ -1 +1 @@
-Subproject commit cd7e07714802c61aa2dbf3850440f3c83cfcf45e
+Subproject commit 4956958f4a91536007644d13f99c07954b9ba76b