mirror of
https://github.com/github/semantic.git
synced 2025-01-03 04:51:57 +03:00
Merge pull request #915 from github/javascript-improvements
JavaScript improvements (and updates tree-sitter across all languages)
This commit is contained in:
commit
2faa62936b
@ -159,6 +159,10 @@ data Category
|
||||
| HashSplatParameter
|
||||
-- | A block parameter, e.g. def foo(&block) in Ruby.
|
||||
| BlockParameter
|
||||
-- | A break statement, e.g. break; in JavaScript.
|
||||
| Break
|
||||
-- | A continue statement, e.g. continue; in JavaScript.
|
||||
| Continue
|
||||
deriving (Eq, Generic, Ord, Show)
|
||||
|
||||
-- Instances
|
||||
@ -244,6 +248,8 @@ instance Arbitrary Category where
|
||||
, pure SplatParameter
|
||||
, pure HashSplatParameter
|
||||
, pure BlockParameter
|
||||
, pure Break
|
||||
, pure Continue
|
||||
, Other <$> arbitrary
|
||||
]
|
||||
|
||||
|
@ -154,6 +154,10 @@ determiner (LeafInfo "else block" _ _) = "an"
|
||||
determiner (LeafInfo "ensure block" _ _) = "an"
|
||||
determiner (LeafInfo "when block" _ _) = "a"
|
||||
determiner (LeafInfo "anonymous function" _ _) = "an"
|
||||
determiner (LeafInfo "break statement" _ _) = "a"
|
||||
determiner (LeafInfo "continue statement" _ _) = "a"
|
||||
determiner (LeafInfo "yield statement" "" _) = "a"
|
||||
determiner (LeafInfo "return statement" "" _) = "a"
|
||||
determiner (BranchInfo bs _ _) = determiner (last bs)
|
||||
determiner _ = "the"
|
||||
|
||||
@ -175,6 +179,10 @@ toLeafInfos leaf = pure . flip JSONSummary (sourceSpan leaf) $ case leaf of
|
||||
(LeafInfo cName@"export statement" termName _) -> toDoc termName <+> toDoc cName
|
||||
(LeafInfo cName@"import statement" termName _) -> toDoc termName <+> toDoc cName
|
||||
(LeafInfo cName@"subshell command" termName _) -> toDoc termName <+> toDoc cName
|
||||
(LeafInfo cName@"break statement" _ _) -> toDoc cName
|
||||
(LeafInfo cName@"continue statement" _ _) -> toDoc cName
|
||||
(LeafInfo cName@"yield statement" "" _) -> toDoc cName
|
||||
(LeafInfo cName@"return statement" "" _) -> toDoc cName
|
||||
LeafInfo{..} -> squotes (toDoc termName) <+> toDoc categoryName
|
||||
node -> panic $ "Expected a leaf info but got a: " <> show node
|
||||
|
||||
@ -224,8 +232,8 @@ toTermName source term = case unwrap term of
|
||||
S.Operator _ -> termNameFromSource term
|
||||
S.Object kvs -> "{ " <> intercalate ", " (toTermName' <$> kvs) <> " }"
|
||||
S.Pair k v -> toKeyName k <> toArgName v
|
||||
S.Return expr -> maybe "empty" toTermName' expr
|
||||
S.Yield expr -> maybe "empty" toTermName' expr
|
||||
S.Return children -> intercalate ", " (termNameFromSource <$> children)
|
||||
S.Yield children -> intercalate ", " (termNameFromSource <$> children)
|
||||
S.Error _ -> termNameFromSource term
|
||||
S.If expr _ -> termNameFromSource expr
|
||||
S.For clauses _ -> termNameFromChildren term clauses
|
||||
@ -249,6 +257,8 @@ toTermName source term = case unwrap term of
|
||||
S.ConditionalAssignment id _ -> toTermName' id
|
||||
S.Negate expr -> toTermName' expr
|
||||
S.Rescue args _ -> intercalate ", " $ toTermName' <$> args
|
||||
S.Break expr -> toTermName' expr
|
||||
S.Continue expr -> toTermName' expr
|
||||
where toTermName' = toTermName source
|
||||
termNameFromChildren term children = termNameFromRange (unionRangesFrom (range term) (range <$> children))
|
||||
termNameFromSource term = termNameFromRange (range term)
|
||||
@ -416,6 +426,8 @@ instance HasCategory Category where
|
||||
C.SplatParameter -> "parameter"
|
||||
C.HashSplatParameter -> "parameter"
|
||||
C.BlockParameter -> "parameter"
|
||||
C.Break -> "break statement"
|
||||
C.Continue -> "continue statement"
|
||||
|
||||
instance HasField fields Category => HasCategory (SyntaxTerm leaf fields) where
|
||||
toCategoryName = toCategoryName . category . extract
|
||||
|
@ -18,7 +18,7 @@ termConstructor
|
||||
-> [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ The child nodes of the term.
|
||||
-> IO (SyntaxTerm Text '[Range, Category, SourceSpan]) -- ^ The resulting term, in IO.
|
||||
termConstructor source sourceSpan name range children = case name of
|
||||
"return_statement" -> withDefaultInfo $ S.Return (listToMaybe children)
|
||||
"return_statement" -> withDefaultInfo $ S.Return children
|
||||
"source_file" -> case children of
|
||||
packageName : rest | category (extract packageName) == Other "package_clause" ->
|
||||
case unwrap packageName of
|
||||
@ -186,4 +186,3 @@ categoryForGoName = \case
|
||||
"type_assertion_expression" -> TypeAssertion
|
||||
"type_conversion_expression" -> TypeConversion
|
||||
s -> Other (toS s)
|
||||
|
||||
|
@ -16,7 +16,7 @@ functions :: [Text]
|
||||
functions = [ "arrow_function", "generator_function", "function" ]
|
||||
|
||||
forStatements :: [Text]
|
||||
forStatements = [ "for_statement", "for_of_statement", "for_in_statement" ]
|
||||
forStatements = [ "for_statement", "for_of_statement", "for_in_statement", "trailing_for_statement", "trailing_for_of_statement", "trailing_for_in_statement" ]
|
||||
|
||||
termConstructor
|
||||
:: Source Char -- ^ The source that the term occurs within.
|
||||
@ -28,7 +28,8 @@ termConstructor
|
||||
termConstructor source sourceSpan name range children
|
||||
| name == "ERROR" = withDefaultInfo (S.Error children)
|
||||
| otherwise = withDefaultInfo $ case (name, children) of
|
||||
("return_statement", _) -> S.Return (listToMaybe children)
|
||||
("return_statement", _) -> S.Return children
|
||||
("trailing_return_statement", _) -> S.Return children
|
||||
("assignment", [ identifier, value ]) -> S.Assignment identifier value
|
||||
("assignment", _ ) -> S.Error children
|
||||
("math_assignment", [ identifier, value ]) -> S.MathAssignment identifier value
|
||||
@ -52,6 +53,7 @@ termConstructor source sourceSpan name range children
|
||||
("var_assignment", [ x, y ]) -> S.VarAssignment x y
|
||||
("var_assignment", _ ) -> S.Error children
|
||||
("var_declaration", _) -> S.Indexed $ toVarDecl <$> children
|
||||
("trailing_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]
|
||||
@ -60,13 +62,21 @@ termConstructor source sourceSpan name range children
|
||||
("pair", _) -> S.Fixed children
|
||||
("comment", _) -> S.Comment . toText $ slice range source
|
||||
("if_statement", expr : rest ) -> S.If expr rest
|
||||
("trailing_if_statement", expr : rest ) -> S.If expr rest
|
||||
("if_statement", _ ) -> S.Error children
|
||||
("trailing_if_statement", _ ) -> S.Error children
|
||||
("while_statement", expr : rest ) -> S.While expr rest
|
||||
("trailing_while_statement", expr : rest ) -> S.While expr rest
|
||||
("while_statement", _ ) -> S.Error children
|
||||
("trailing_while_statement", _ ) -> S.Error children
|
||||
("do_statement", [ expr, body ]) -> S.DoWhile expr body
|
||||
("trailing_do_statement", [ expr, body ]) -> S.DoWhile expr body
|
||||
("do_statement", _ ) -> S.Error children
|
||||
("trailing_do_statement", _ ) -> S.Error children
|
||||
("throw_statement", [ expr ]) -> S.Throw expr
|
||||
("trailing_throw_statement", [ expr ]) -> S.Throw expr
|
||||
("throw_statment", _ ) -> S.Error children
|
||||
("trailing_throw_statment", _ ) -> S.Error children
|
||||
("new_expression", [ expr ]) -> S.Constructor expr
|
||||
("new_expression", _ ) -> S.Error children
|
||||
("try_statement", _) -> case children of
|
||||
@ -92,6 +102,8 @@ termConstructor source sourceSpan name range children
|
||||
S.Indexed _ -> S.Export Nothing (toList (unwrap statements))
|
||||
_ -> S.Export (Just statements) []
|
||||
("export_statement", _ ) -> S.Error children
|
||||
("break_statement", [ expr ] ) -> S.Break expr
|
||||
("yield_statement", _ ) -> S.Yield children
|
||||
_ | name `elem` forStatements -> case unsnoc children of
|
||||
Just (exprs, body) -> S.For exprs [body]
|
||||
_ -> S.Error children
|
||||
@ -114,6 +126,7 @@ categoryForJavaScriptProductionName :: Text -> Category
|
||||
categoryForJavaScriptProductionName name = case name of
|
||||
"object" -> Object
|
||||
"expression_statement" -> ExpressionStatements
|
||||
"trailing_expression_statement" -> ExpressionStatements
|
||||
"this_expression" -> Identifier
|
||||
"null" -> Identifier
|
||||
"undefined" -> Identifier
|
||||
@ -125,13 +138,18 @@ categoryForJavaScriptProductionName name = case name of
|
||||
"delete_op" -> Operator -- delete operator, e.g. delete x[2].
|
||||
"type_op" -> Operator -- type operator, e.g. typeof Object.
|
||||
"void_op" -> Operator -- void operator, e.g. void 2.
|
||||
"for_statement" -> For
|
||||
"trailing_for_statement" -> For
|
||||
"for_in_statement" -> For
|
||||
"trailing_for_in_statement" -> For
|
||||
"for_of_statement" -> For
|
||||
"trailing_for_of_statement" -> For
|
||||
"new_expression" -> Constructor
|
||||
"class" -> Class
|
||||
"catch" -> Catch
|
||||
"finally" -> Finally
|
||||
"if_statement" -> If
|
||||
"trailing_if_statement" -> If
|
||||
"empty_statement" -> Empty
|
||||
"program" -> Program
|
||||
"ERROR" -> Error
|
||||
@ -155,17 +173,21 @@ categoryForJavaScriptProductionName name = case name of
|
||||
"template_string" -> TemplateString
|
||||
"var_assignment" -> VarAssignment
|
||||
"var_declaration" -> VarDecl
|
||||
"trailing_var_declaration" -> VarDecl
|
||||
"switch_statement" -> Switch
|
||||
"math_assignment" -> MathAssignment
|
||||
"case" -> Case
|
||||
"true" -> Boolean
|
||||
"false" -> Boolean
|
||||
"ternary" -> Ternary
|
||||
"for_statement" -> For
|
||||
"while_statement" -> While
|
||||
"trailing_while_statement" -> While
|
||||
"do_statement" -> DoWhile
|
||||
"trailing_do_statement" -> DoWhile
|
||||
"return_statement" -> Return
|
||||
"trailing_return_statement" -> Return
|
||||
"throw_statement" -> Throw
|
||||
"trailing_throw_statement" -> Throw
|
||||
"try_statement" -> Try
|
||||
"method_definition" -> Method
|
||||
"comment" -> Comment
|
||||
@ -173,4 +195,7 @@ categoryForJavaScriptProductionName name = case name of
|
||||
"rel_op" -> RelationalOperator
|
||||
"import_statement" -> Import
|
||||
"export_statement" -> Export
|
||||
"break_statement" -> Break
|
||||
"continue_statement" -> Continue
|
||||
"yield_statement" -> Yield
|
||||
_ -> Other name
|
||||
|
@ -30,7 +30,7 @@ termConstructor source sourceSpan name range children
|
||||
condition <- withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)
|
||||
withDefaultInfo $ S.If condition [lhs]
|
||||
_ -> withDefaultInfo $ S.Error children
|
||||
| name == "unless_statement" = case children of
|
||||
| name == "unless" = case children of
|
||||
( expr : rest ) -> do
|
||||
condition <- withRecord (setCategory (extract expr) Negate) (S.Negate expr)
|
||||
withDefaultInfo $ S.If condition rest
|
||||
@ -40,7 +40,7 @@ termConstructor source sourceSpan name range children
|
||||
condition <- withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)
|
||||
withDefaultInfo $ S.While condition [lhs]
|
||||
_ -> withDefaultInfo $ S.Error children
|
||||
| name == "until_statement" = case children of
|
||||
| name == "until" = case children of
|
||||
( expr : rest ) -> do
|
||||
condition <- withRecord (setCategory (extract expr) Negate) (S.Negate expr)
|
||||
withDefaultInfo $ S.While condition rest
|
||||
@ -57,7 +57,7 @@ termConstructor source sourceSpan name range children
|
||||
("array", _ ) -> S.Array children
|
||||
("assignment", [ identifier, value ]) -> S.Assignment identifier value
|
||||
("assignment", _ ) -> S.Error children
|
||||
("begin_statement", _ ) -> case partition (\x -> category (extract x) == Rescue) children of
|
||||
("begin", _ ) -> 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 ]
|
||||
@ -69,19 +69,19 @@ termConstructor source sourceSpan name range children
|
||||
[ 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
|
||||
("case", expr : body ) -> S.Switch expr body
|
||||
("case", _ ) -> S.Error children
|
||||
("when", condition : body ) -> S.Case condition body
|
||||
("when", _ ) -> S.Error children
|
||||
("class", [ identifier, superclass, definitions ]) -> S.Class identifier (Just superclass) (toList (unwrap definitions))
|
||||
("class", [ identifier, definitions ]) -> S.Class identifier Nothing (toList (unwrap definitions))
|
||||
("class", _ ) -> S.Error children
|
||||
("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 children of
|
||||
("method_call", _ ) -> case children of
|
||||
member : args | MemberAccess <- category (extract member) -> case toList (unwrap member) of
|
||||
[target, method] -> S.MethodCall target method (toList . unwrap =<< args)
|
||||
_ -> S.Error children
|
||||
@ -90,25 +90,25 @@ termConstructor source sourceSpan name range children
|
||||
("hash", _ ) -> S.Object $ foldMap toTuple children
|
||||
("if_modifier", [ lhs, condition ]) -> S.If condition [lhs]
|
||||
("if_modifier", _ ) -> S.Error children
|
||||
("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
|
||||
("if", condition : body ) -> S.If condition body
|
||||
("if", _ ) -> S.Error children
|
||||
("elsif", condition : body ) -> S.If condition body
|
||||
("elsif", _ ) -> 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
|
||||
("for", lhs : expr : rest ) -> S.For [lhs, expr] rest
|
||||
("for", _ ) -> 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", _ ) -> case children of
|
||||
("method", _ ) -> 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
|
||||
("module", identifier : body ) -> S.Module identifier body
|
||||
("module", _ ) -> S.Error children
|
||||
("rescue", _ ) -> case children of
|
||||
args : lastException : rest
|
||||
| RescueArgs <- category (extract args)
|
||||
, RescuedException <- category (extract lastException) -> S.Rescue (toList (unwrap args) <> [lastException]) rest
|
||||
@ -117,12 +117,12 @@ termConstructor source sourceSpan name range children
|
||||
body -> S.Rescue [] body
|
||||
("rescue_modifier", [lhs, rhs] ) -> S.Rescue [lhs] [rhs]
|
||||
("rescue_modifier", _ ) -> S.Error children
|
||||
("return_statement", _ ) -> S.Return (listToMaybe children)
|
||||
("return", _ ) -> S.Return 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)
|
||||
("while", expr : rest ) -> S.While expr rest
|
||||
("while", _ ) -> S.Error children
|
||||
("yield", _ ) -> S.Yield children
|
||||
_ | name `elem` operators -> S.Operator children
|
||||
_ | name `elem` functions -> case children of
|
||||
[ body ] -> S.AnonymousFunction [] [body]
|
||||
@ -146,63 +146,63 @@ categoryForRubyName = \case
|
||||
"argument_pair" -> ArgumentPair
|
||||
"array" -> ArrayLiteral
|
||||
"assignment" -> Assignment
|
||||
"begin_statement" -> Begin
|
||||
"begin" -> Begin
|
||||
"bitwise_and" -> BitwiseOperator -- bitwise and, e.g &.
|
||||
"bitwise_or" -> BitwiseOperator -- bitwise or, e.g. ^, |.
|
||||
"block_parameter" -> BlockParameter
|
||||
"boolean_and" -> BooleanOperator -- boolean and, e.g. &&.
|
||||
"boolean_or" -> BooleanOperator -- boolean or, e.g. &&.
|
||||
"boolean" -> Boolean
|
||||
"case_statement" -> Case
|
||||
"class_declaration" -> Class
|
||||
"case" -> Case
|
||||
"class" -> Class
|
||||
"comment" -> Comment
|
||||
"comparison" -> RelationalOperator -- comparison operator, e.g. <, <=, >=, >.
|
||||
"conditional_assignment" -> ConditionalAssignment
|
||||
"conditional" -> Ternary
|
||||
"element_reference" -> SubscriptAccess
|
||||
"else_block" -> Else
|
||||
"elsif_block" -> Elsif
|
||||
"ensure_block" -> Ensure
|
||||
"else" -> Else
|
||||
"elsif" -> Elsif
|
||||
"ensure" -> Ensure
|
||||
"ERROR" -> Error
|
||||
"float" -> NumberLiteral
|
||||
"for_statement" -> For
|
||||
"for" -> For
|
||||
"formal_parameters" -> Params
|
||||
"function_call" -> FunctionCall
|
||||
"method_call" -> FunctionCall
|
||||
"function" -> Function
|
||||
"hash_splat_parameter" -> HashSplatParameter
|
||||
"hash" -> Object
|
||||
"identifier" -> Identifier
|
||||
"if_modifier" -> If
|
||||
"if_statement" -> If
|
||||
"if" -> If
|
||||
"integer" -> IntegerLiteral
|
||||
"interpolation" -> Interpolation
|
||||
"keyword_parameter" -> KeywordParameter
|
||||
"math_assignment" -> MathAssignment
|
||||
"member_access" -> MemberAccess
|
||||
"method_declaration" -> Method
|
||||
"module_declaration" -> Module
|
||||
"method" -> Method
|
||||
"module" -> Module
|
||||
"nil" -> Identifier
|
||||
"optional_parameter" -> OptionalParameter
|
||||
"or" -> BooleanOperator
|
||||
"program" -> Program
|
||||
"regex" -> Regex
|
||||
"relational" -> RelationalOperator -- relational operator, e.g. ==, !=, ===, <=>, =~, !~.
|
||||
"rescue_arguments" -> RescueArgs
|
||||
"rescue_block" -> Rescue
|
||||
"exceptions" -> RescueArgs
|
||||
"rescue" -> Rescue
|
||||
"rescue_modifier" -> RescueModifier
|
||||
"rescued_exception" -> RescuedException
|
||||
"return_statement" -> Return
|
||||
"exception_variable" -> RescuedException
|
||||
"return" -> Return
|
||||
"shift" -> BitwiseOperator -- bitwise shift, e.g <<, >>.
|
||||
"splat_parameter" -> SplatParameter
|
||||
"string" -> StringLiteral
|
||||
"subshell" -> Subshell
|
||||
"symbol" -> SymbolLiteral
|
||||
"unless_modifier" -> Unless
|
||||
"unless_statement" -> Unless
|
||||
"unless" -> Unless
|
||||
"until_modifier" -> Until
|
||||
"until_statement" -> Until
|
||||
"when_block" -> When
|
||||
"until" -> Until
|
||||
"when" -> When
|
||||
"while_modifier" -> While
|
||||
"while_statement" -> While
|
||||
"while" -> While
|
||||
"yield" -> Yield
|
||||
s -> Other s
|
||||
|
@ -143,4 +143,6 @@ syntaxToTermField syntax = case syntax of
|
||||
S.Defer cases -> childrenFields cases
|
||||
S.TypeAssertion a b -> childrenFields [a, b]
|
||||
S.TypeConversion a b -> childrenFields [a, b]
|
||||
S.Break expr -> [ "expression" .= expr ]
|
||||
S.Continue expr -> [ "expression" .= expr ]
|
||||
where childrenFields c = [ "children" .= c ]
|
||||
|
@ -112,6 +112,8 @@ styleName category = "category-" <> case category of
|
||||
C.SplatParameter -> "splat_param"
|
||||
C.HashSplatParameter -> "hash_splat_param"
|
||||
C.BlockParameter -> "block_param"
|
||||
C.Break -> "break_statement"
|
||||
C.Continue -> "continue_statement"
|
||||
|
||||
-- | Pick the class name for a split patch.
|
||||
splitPatchToClassName :: SplitPatch a -> AttributeValue
|
||||
|
@ -60,7 +60,7 @@ data Syntax a f
|
||||
| For [f] [f]
|
||||
| DoWhile { doWhileBody :: f, doWhileExpr :: f }
|
||||
| While { whileExpr :: f, whileBody :: [f] }
|
||||
| Return (Maybe f)
|
||||
| Return [f]
|
||||
| Throw f
|
||||
| Constructor f
|
||||
-- | TODO: Is it a problem that in Ruby, this pattern can work for method def too?
|
||||
@ -79,7 +79,7 @@ data Syntax a f
|
||||
| Export (Maybe f) [f]
|
||||
-- | A conditional assignment represents expressions whose operator classifies as conditional (e.g. ||= or &&=).
|
||||
| ConditionalAssignment { conditionalAssignmentId :: f, value :: f }
|
||||
| Yield (Maybe f)
|
||||
| Yield [f]
|
||||
-- | A negation of a single expression.
|
||||
| Negate f
|
||||
-- | A rescue block has a list of arguments to rescue and a list of expressions.
|
||||
@ -88,6 +88,8 @@ data Syntax a f
|
||||
| Defer f
|
||||
| TypeAssertion f f
|
||||
| TypeConversion f f
|
||||
| Break f
|
||||
| Continue f
|
||||
deriving (Eq, Foldable, Functor, Generic, Generic1, Mergeable, Ord, Show, Traversable, ToJSON)
|
||||
|
||||
|
||||
|
@ -40,7 +40,7 @@
|
||||
"+end"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "51729c359e350d71395532126c23bfed960f2373..eb8e4745aa2692c20519254d7b8d27b3a2c07cac"
|
||||
"shas": "a8b440ad76232e4e95f5a5ed53b9b6604ece8a17..4469095014f7bc3f2ba06bba93197b7113965a36"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-if-replacement-insert-test",
|
||||
@ -121,7 +121,7 @@
|
||||
" elsif quux"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "eb8e4745aa2692c20519254d7b8d27b3a2c07cac..a0d707f1e50df11d0aa4d3407dfcf79fad65acc6"
|
||||
"shas": "4469095014f7bc3f2ba06bba93197b7113965a36..49f95d96fcf4b3e1ddc5d64c6d19c1f1415aa21f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-if-delete-insert-test",
|
||||
@ -178,28 +178,13 @@
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
7,
|
||||
1
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'quux' elsif block in the 'foo' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
6,
|
||||
3
|
||||
],
|
||||
"end": [
|
||||
6,
|
||||
6
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'bat' identifier in the 'foo' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
@ -242,7 +227,7 @@
|
||||
" bar"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "a0d707f1e50df11d0aa4d3407dfcf79fad65acc6..b9ef26ef27b3cf5ad0e522a145ede60f9b4f3dc2"
|
||||
"shas": "49f95d96fcf4b3e1ddc5d64c6d19c1f1415aa21f..69de797721bf90b5e163efddf6c21683973e91e5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-if-replacement-test",
|
||||
@ -299,28 +284,13 @@
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
7,
|
||||
1
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'quux' elsif block in the 'x' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
6,
|
||||
3
|
||||
],
|
||||
"end": [
|
||||
6,
|
||||
6
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'bat' identifier in the 'x' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
@ -363,7 +333,7 @@
|
||||
" bar"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "b9ef26ef27b3cf5ad0e522a145ede60f9b4f3dc2..af72ae7656106dce11ffcbd6c2a31e9a756b0342"
|
||||
"shas": "69de797721bf90b5e163efddf6c21683973e91e5..c4dc260bbc97bb7f7c90d41a7ee7418e31529715"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-if-delete-replacement-test",
|
||||
@ -421,7 +391,7 @@
|
||||
" end"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "af72ae7656106dce11ffcbd6c2a31e9a756b0342..2aef901d538d790e42fec0a2a6b1522d8b4fce9e"
|
||||
"shas": "c4dc260bbc97bb7f7c90d41a7ee7418e31529715..941d12bbe9281602e9f778ef87716fa0cdc94f6c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-if-delete-test",
|
||||
@ -468,7 +438,7 @@
|
||||
" if y then"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "2aef901d538d790e42fec0a2a6b1522d8b4fce9e..bd1fd56e20054df058e8bc8d3e2dd0d523ecce08"
|
||||
"shas": "941d12bbe9281602e9f778ef87716fa0cdc94f6c..79311ce946c9650610644371262924744f9acecc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-if-delete-rest-test",
|
||||
@ -524,5 +494,5 @@
|
||||
"-end"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "bd1fd56e20054df058e8bc8d3e2dd0d523ecce08..4fed48f0abf8058f93dbb4c7361358c434c9bb6d"
|
||||
"shas": "79311ce946c9650610644371262924744f9acecc..6745758f03dc308eff3e95e8876445225bcdf49e"
|
||||
}]
|
@ -8,7 +8,7 @@
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
7
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
@ -16,7 +16,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'x[y]()' defer statement"
|
||||
"summary": "Added the 'x[y]()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -50,7 +50,7 @@
|
||||
"+go x.y()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "201c2f06d17d14e12c9861e2a94372fc41441178..4c2c5d9bf86b0e00910db4151d8cb1be6e261245"
|
||||
"shas": "aa6d103c0bde1c5cd7c122b6a597939f9920694d..39d794d96184f5c24d53575d9acf0c1408848019"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-go-and-defer-statements-replacement-insert-test",
|
||||
@ -116,6 +116,36 @@
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'x[y]()' go statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
5,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
12
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'x[y]()' defer statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
7
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
12
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'x[y]()' function call"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -138,7 +168,7 @@
|
||||
" go x.y()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "4c2c5d9bf86b0e00910db4151d8cb1be6e261245..0af27bad18af4c3f10e18adf6824bc24be7cdf18"
|
||||
"shas": "39d794d96184f5c24d53575d9acf0c1408848019..f00940bceca8647dfc5c03a16d11fa77b65605ab"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-go-and-defer-statements-delete-insert-test",
|
||||
@ -275,7 +305,7 @@
|
||||
" defer x.y()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "0af27bad18af4c3f10e18adf6824bc24be7cdf18..e8853de747eee3ecdd93e3344be1e54dbc28e8fe"
|
||||
"shas": "f00940bceca8647dfc5c03a16d11fa77b65605ab..a438dd8c1ac73cefd028b38d896c9e7150693fda"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-go-and-defer-statements-replacement-test",
|
||||
@ -412,7 +442,7 @@
|
||||
" defer x.y()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "e8853de747eee3ecdd93e3344be1e54dbc28e8fe..baf0c568b56a2909465365b10b1764e574ffdcbf"
|
||||
"shas": "a438dd8c1ac73cefd028b38d896c9e7150693fda..be9ca54744a56600853a24a3574f6a9372317a4e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-go-and-defer-statements-delete-replacement-test",
|
||||
@ -532,13 +562,28 @@
|
||||
"+go c.d()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "baf0c568b56a2909465365b10b1764e574ffdcbf..8449fd5df5a995e61d8ca8b450f83468e79a5246"
|
||||
"shas": "be9ca54744a56600853a24a3574f6a9372317a4e..8aed3cad89b295cbb44d0af3d14a133805b21092"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-go-and-defer-statements-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"go-and-defer-statements.go": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
7
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
12
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'a[b]()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
@ -568,6 +613,21 @@
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'x[y]()' go statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
3,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
3,
|
||||
12
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'a[b]()' defer statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -588,7 +648,7 @@
|
||||
" go c.d()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "8449fd5df5a995e61d8ca8b450f83468e79a5246..129278c1c54e5bcd112a0f7bc5a4876b0890b5a9"
|
||||
"shas": "8aed3cad89b295cbb44d0af3d14a133805b21092..2597c988897b6b96cb121f2abfda7a34f3a2e78a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-go-and-defer-statements-delete-rest-test",
|
||||
@ -600,7 +660,7 @@
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
7
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
@ -608,7 +668,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'a[b]()' defer statement"
|
||||
"summary": "Deleted the 'a[b]()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -642,5 +702,5 @@
|
||||
"-go c.d()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "129278c1c54e5bcd112a0f7bc5a4876b0890b5a9..13fa148e00739eba43f10562e024e15d2fc7e5d9"
|
||||
"shas": "2597c988897b6b96cb121f2abfda7a34f3a2e78a..1b6e0feb56e5cdb7ad291617f2f0435417e65665"
|
||||
}]
|
||||
|
@ -34,7 +34,7 @@
|
||||
"+a.b.c()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "b8520b47d7e23a8b805613ba5e28d123748a7e86..53e9575bb4a95b6a13a9289b3cb198389c3c5018"
|
||||
"shas": "1b6e0feb56e5cdb7ad291617f2f0435417e65665..1cabbfb616bb7f16666511f145e8709354b162c1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-selector-expressions-replacement-insert-test",
|
||||
@ -70,6 +70,36 @@
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'a[b][c]()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
3,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
3,
|
||||
8
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'a[b][c]()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
8
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'a[b][c]()' function call"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -89,7 +119,7 @@
|
||||
" a.b.c()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "53e9575bb4a95b6a13a9289b3cb198389c3c5018..05337c7344ffd11906be9b6603043c1bcf0f7dff"
|
||||
"shas": "1cabbfb616bb7f16666511f145e8709354b162c1..9cd2e1fa67eaf8b7701eb693cbde0abf05a9acf2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-selector-expressions-delete-insert-test",
|
||||
@ -196,7 +226,7 @@
|
||||
" a.b.c()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "05337c7344ffd11906be9b6603043c1bcf0f7dff..4bcafdd401ffbfb0e29802793ed59f20908986a6"
|
||||
"shas": "9cd2e1fa67eaf8b7701eb693cbde0abf05a9acf2..87e2a67ff089313ce73948c33f5fed26678e69e6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-selector-expressions-replacement-test",
|
||||
@ -303,7 +333,7 @@
|
||||
" a.b.c()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "4bcafdd401ffbfb0e29802793ed59f20908986a6..1763e869f9b7050dc5703f293808233c46910062"
|
||||
"shas": "87e2a67ff089313ce73948c33f5fed26678e69e6..8288366db7745d5e945597239e1e3e9e7384f986"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-selector-expressions-delete-replacement-test",
|
||||
@ -374,13 +404,28 @@
|
||||
"+x.y.z()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "1763e869f9b7050dc5703f293808233c46910062..562bbf82089ed1bc7d77c4698451746939455f51"
|
||||
"shas": "8288366db7745d5e945597239e1e3e9e7384f986..6320cb015ad06170d57469ad6117980fcf530917"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-selector-expressions-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"selector-expressions.go": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
8
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'x[y][z]()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
@ -395,6 +440,21 @@
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'a[b][c]()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
8
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'x[y][z]()' function call"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -413,7 +473,7 @@
|
||||
" x.y.z()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "562bbf82089ed1bc7d77c4698451746939455f51..3ea379fb7d49d67e17b2bd53b58af0298c055ccc"
|
||||
"shas": "6320cb015ad06170d57469ad6117980fcf530917..64072b885bd8b401823412418b0a634151fb012c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-selector-expressions-delete-rest-test",
|
||||
@ -451,5 +511,5 @@
|
||||
"-x.y.z()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "3ea379fb7d49d67e17b2bd53b58af0298c055ccc..bef4b21e0fe9824b79e8b12bfa32867c8a4433a7"
|
||||
"shas": "64072b885bd8b401823412418b0a634151fb012c..5e49cf8bc49a6acceee67258f44392614d3e2807"
|
||||
}]
|
||||
|
@ -34,7 +34,7 @@
|
||||
"+x.(z.Person)"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "fff4b5e3aa207b2f8d5dc8ddb03b550f79baec95..7cdaee711fdf7f7a97fc3269e28626252a4dc3dc"
|
||||
"shas": "47d2e77075bea143df064341695111f434390787..012b1aebf2431d713e5287b10792aa564b72d6bc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-assertion-expressions-replacement-insert-test",
|
||||
@ -70,6 +70,36 @@
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'x.(z.Person)' type assertion statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
3,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
3,
|
||||
13
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'x.(z.Person)' type assertion statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
13
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'x.(z.Person)' type assertion statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -89,7 +119,7 @@
|
||||
" x.(z.Person)"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "7cdaee711fdf7f7a97fc3269e28626252a4dc3dc..2bccd29b12d301d0fa0744e890ae3afdba1f43bc"
|
||||
"shas": "012b1aebf2431d713e5287b10792aa564b72d6bc..65901508a1a56b8fd65f1c704be9ebdb7c0e9962"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-assertion-expressions-delete-insert-test",
|
||||
@ -196,7 +226,7 @@
|
||||
" x.(z.Person)"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "2bccd29b12d301d0fa0744e890ae3afdba1f43bc..b774e03f1513e1139f22bbc3e116e2ff17168247"
|
||||
"shas": "65901508a1a56b8fd65f1c704be9ebdb7c0e9962..cf149b0f32f8c6e2111d7e24f6384ef8a7465ed3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-assertion-expressions-replacement-test",
|
||||
@ -303,7 +333,7 @@
|
||||
" x.(z.Person)"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "b774e03f1513e1139f22bbc3e116e2ff17168247..596b57a4b9a75038c3f5594caa3561a52de5dc16"
|
||||
"shas": "cf149b0f32f8c6e2111d7e24f6384ef8a7465ed3..2785ff758a864fb059f1d3a640356184e685c7ae"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-assertion-expressions-delete-replacement-test",
|
||||
@ -374,13 +404,28 @@
|
||||
"+b.(c.Dog)"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "596b57a4b9a75038c3f5594caa3561a52de5dc16..b9105039f8d9f039416e98ced5b9e80b8f7c7d40"
|
||||
"shas": "2785ff758a864fb059f1d3a640356184e685c7ae..2747f7daa786f2a814e7e8381120d838050d1d89"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-assertion-expressions-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-assertion-expressions.go": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
10
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'b.(c.Dog)' type assertion statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
@ -395,6 +440,21 @@
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'x.(z.Person)' type assertion statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
10
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'b.(c.Dog)' type assertion statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -413,7 +473,7 @@
|
||||
" b.(c.Dog)"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "b9105039f8d9f039416e98ced5b9e80b8f7c7d40..868316791e7a76d17ffd45113d8b0a74886f8c90"
|
||||
"shas": "2747f7daa786f2a814e7e8381120d838050d1d89..f710680272400bb3cfcdca84cbc9a46dc3e136ba"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-assertion-expressions-delete-rest-test",
|
||||
@ -451,5 +511,5 @@
|
||||
"-b.(c.Dog)"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "868316791e7a76d17ffd45113d8b0a74886f8c90..5f76f266d80a0de28bb0535282f740664c37c11d"
|
||||
"shas": "f710680272400bb3cfcdca84cbc9a46dc3e136ba..aa6d103c0bde1c5cd7c122b6a597939f9920694d"
|
||||
}]
|
||||
|
@ -113,7 +113,7 @@
|
||||
"+ )"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "ba18dfa94bdd542c6e02a9537056dd589dd722da..e00fa9b114014263f5eb860c1f568232d8c2e636"
|
||||
"shas": "e560ba24e6b3318aeaaa38fbba2567add6762706..bae5319a920b125fee9eaf9759a92aa5da2e3532"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-declarations-replacement-insert-test",
|
||||
@ -433,7 +433,7 @@
|
||||
" a b"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "e00fa9b114014263f5eb860c1f568232d8c2e636..df0f0782bba768dcdd8cd44c995b372509bc946c"
|
||||
"shas": "bae5319a920b125fee9eaf9759a92aa5da2e3532..e1cbc86ed6adfff25935ae2fde6e52e0f7944faf"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-declarations-delete-insert-test",
|
||||
@ -930,7 +930,7 @@
|
||||
" type ("
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "df0f0782bba768dcdd8cd44c995b372509bc946c..cfe798aea18d3224e069fa338a9ffbf7e8596517"
|
||||
"shas": "e1cbc86ed6adfff25935ae2fde6e52e0f7944faf..fb8f71e56f7c782c5c103939810a573235d96eed"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-declarations-replacement-test",
|
||||
@ -1427,7 +1427,7 @@
|
||||
" type ("
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "cfe798aea18d3224e069fa338a9ffbf7e8596517..92756bc9c8de8ac798d9c5a96fed709990ef6f26"
|
||||
"shas": "fb8f71e56f7c782c5c103939810a573235d96eed..5b0a2d7fcff950132d300c821807689289a9953a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-declarations-delete-replacement-test",
|
||||
@ -1524,6 +1524,21 @@
|
||||
},
|
||||
"summary": "Added the 'd' identifier"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
6,
|
||||
6
|
||||
],
|
||||
"end": [
|
||||
6,
|
||||
7
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'a' identifier"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
@ -1569,21 +1584,6 @@
|
||||
},
|
||||
"summary": "Added the ''\n' ERROR"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
8,
|
||||
2
|
||||
],
|
||||
"end": [
|
||||
8,
|
||||
3
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'a' identifier"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
@ -1992,7 +1992,7 @@
|
||||
" )"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "92756bc9c8de8ac798d9c5a96fed709990ef6f26..e72df0b090fe30087548209c4dc301b9729fc594"
|
||||
"shas": "5b0a2d7fcff950132d300c821807689289a9953a..28961b1c59a82635b9174f3e1a492635af8449ce"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-declarations-delete-test",
|
||||
@ -2112,7 +2112,7 @@
|
||||
" a' b'"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "e72df0b090fe30087548209c4dc301b9729fc594..f66688eab0c288423dcf1b1ead3f534f4272125b"
|
||||
"shas": "28961b1c59a82635b9174f3e1a492635af8449ce..574d1837a6533c222449e99ca08b246dfd4db51b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-type-declarations-delete-rest-test",
|
||||
@ -2319,5 +2319,5 @@
|
||||
"- )"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "f66688eab0c288423dcf1b1ead3f534f4272125b..eab68be4fe73c7ea63793058e38316a7eab75064"
|
||||
"shas": "574d1837a6533c222449e99ca08b246dfd4db51b..47d2e77075bea143df064341695111f434390787"
|
||||
}]
|
||||
|
@ -23,7 +23,7 @@
|
||||
"insert": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
2
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
@ -31,7 +31,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'identifier()' function call"
|
||||
"summary": "Added the 'foo()' function call"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -50,7 +50,7 @@
|
||||
"+*foo()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "3403cd75b5874d1bc6c4c3c737525b7bd1271113..25caa48897bbba94e3ebd10df0cab8c1af27c26d"
|
||||
"shas": "0c22b7aa63a02fe2ddea7a2e3531e1bf778729a1..a853d892401554051aac78581481f205834001a0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-unary-expressions-replacement-insert-test",
|
||||
@ -77,7 +77,7 @@
|
||||
"insert": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
2
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
@ -85,7 +85,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'identifier()' function call"
|
||||
"summary": "Added the 'bar()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -102,12 +102,27 @@
|
||||
},
|
||||
"summary": "Added the 'a' identifier"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
4
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
5
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'a' identifier"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
4,
|
||||
1
|
||||
2
|
||||
],
|
||||
"end": [
|
||||
4,
|
||||
@ -115,7 +130,22 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'identifier()' function call"
|
||||
"summary": "Added the 'foo()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
5,
|
||||
4
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
5
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'a' identifier"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -138,7 +168,7 @@
|
||||
" *foo()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "25caa48897bbba94e3ebd10df0cab8c1af27c26d..75a33545386bf76a55b02340bd336b00602e323e"
|
||||
"shas": "a853d892401554051aac78581481f205834001a0..bad62bb53ba866eebb82de0daba4d2af96bada50"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-unary-expressions-delete-insert-test",
|
||||
@ -197,7 +227,7 @@
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'bar' identifier with the 'foo' identifier in the identifier() function call"
|
||||
"summary": "Replaced the 'bar' identifier with the 'foo' identifier in the foo() function call"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -221,7 +251,7 @@
|
||||
" !<-a"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "75a33545386bf76a55b02340bd336b00602e323e..32474c2bac0758793a5ff0f2139cab878545163a"
|
||||
"shas": "bad62bb53ba866eebb82de0daba4d2af96bada50..b3d8517142703695ff4ae6bbbfdae7a8131d62e3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-unary-expressions-replacement-test",
|
||||
@ -280,7 +310,7 @@
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'foo' identifier with the 'bar' identifier in the identifier() function call"
|
||||
"summary": "Replaced the 'foo' identifier with the 'bar' identifier in the bar() function call"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -304,7 +334,7 @@
|
||||
" !<-a"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "32474c2bac0758793a5ff0f2139cab878545163a..36454e266744a461ca2dd6934a061dc63a7c7a63"
|
||||
"shas": "b3d8517142703695ff4ae6bbbfdae7a8131d62e3..851012d113a37b9c98e94b82cd1e32ebdc8be638"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-unary-expressions-delete-replacement-test",
|
||||
@ -331,7 +361,7 @@
|
||||
"delete": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
2
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
@ -339,7 +369,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'identifier()' function call"
|
||||
"summary": "Deleted the 'bar()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -361,7 +391,7 @@
|
||||
"delete": {
|
||||
"start": [
|
||||
4,
|
||||
1
|
||||
2
|
||||
],
|
||||
"end": [
|
||||
4,
|
||||
@ -369,7 +399,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'identifier()' function call"
|
||||
"summary": "Deleted the 'foo()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -391,7 +421,7 @@
|
||||
"insert": {
|
||||
"start": [
|
||||
4,
|
||||
1
|
||||
2
|
||||
],
|
||||
"end": [
|
||||
4,
|
||||
@ -399,7 +429,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'identifier()' function call"
|
||||
"summary": "Added the 'bar()' function call"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -424,13 +454,28 @@
|
||||
"+*bar()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "36454e266744a461ca2dd6934a061dc63a7c7a63..2c0c14abd00ce4615876508894c87c15ad9f49e3"
|
||||
"shas": "851012d113a37b9c98e94b82cd1e32ebdc8be638..163450da5968971b4c4d6ee24b6ffc76e87ff860"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-unary-expressions-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"unary-expressions.go": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
4
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
5
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'b' identifier"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
@ -451,7 +496,7 @@
|
||||
"delete": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
2
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
@ -459,7 +504,22 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'identifier()' function call"
|
||||
"summary": "Deleted the 'foo()' function call"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
3,
|
||||
4
|
||||
],
|
||||
"end": [
|
||||
3,
|
||||
5
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'b' identifier"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -480,7 +540,7 @@
|
||||
" *bar()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "2c0c14abd00ce4615876508894c87c15ad9f49e3..742cb3cf4d2b7f71864c7795fd3307b8775538b3"
|
||||
"shas": "163450da5968971b4c4d6ee24b6ffc76e87ff860..f47634134cc46cd539cef45bcf6090feb116ebb9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-unary-expressions-delete-rest-test",
|
||||
@ -507,7 +567,7 @@
|
||||
"delete": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
2
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
@ -515,7 +575,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'identifier()' function call"
|
||||
"summary": "Deleted the 'bar()' function call"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -534,5 +594,5 @@
|
||||
"-*bar()"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "742cb3cf4d2b7f71864c7795fd3307b8775538b3..ecfd8333e0e37929a8029b0c03cec13c31e0f692"
|
||||
"shas": "f47634134cc46cd539cef45bcf6090feb116ebb9..e560ba24e6b3318aeaaa38fbba2567add6762706"
|
||||
}]
|
||||
|
292
test/corpus/diff-summaries/javascript/break.json
Normal file
292
test/corpus/diff-summaries/javascript/break.json
Normal file
@ -0,0 +1,292 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-break-setup-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"break.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
50
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'i = 0; i < 10; i++' for statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"break.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/break.js b/break.js",
|
||||
"index e69de29b..3f583e3d 100644",
|
||||
"--- a/break.js",
|
||||
"+++ b/break.js",
|
||||
"@@ -0,0 +1 @@",
|
||||
"+for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "0e81c586bea55e0eeb46e3422b25ccba96c7d9ea..d86036d38621253021f5fde6256a16a5d58ffd49"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-break-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"break.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
49
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added a break statement in the 'i === 4' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
41
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
45
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the '{ }' object in the 'i === 4' if statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"break.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/break.js b/break.js",
|
||||
"index 3f583e3d..629dfa91 100644",
|
||||
"--- a/break.js",
|
||||
"+++ b/break.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-for (i = 0; i < 10; i++) { if (i === 4) { }; i }",
|
||||
"+for (i = 0; i < 10; i++) { if (i === 4) { break; }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "d86036d38621253021f5fde6256a16a5d58ffd49..c2a0cadf8477ba2c7525fba7c37923afd994ad15"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-break-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"break.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
52
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added a continue statement in the 'i === 4' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
49
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted a break statement in the 'i === 4' if statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"break.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/break.js b/break.js",
|
||||
"index 629dfa91..16ebcc57 100644",
|
||||
"--- a/break.js",
|
||||
"+++ b/break.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-for (i = 0; i < 10; i++) { if (i === 4) { break; }; i }",
|
||||
"+for (i = 0; i < 10; i++) { if (i === 4) { continue; }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "c2a0cadf8477ba2c7525fba7c37923afd994ad15..3bcd48f5d5894250de6349c4ca5272b3ae92fa6d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-break-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"break.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
49
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added a break statement in the 'i === 4' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
52
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted a continue statement in the 'i === 4' if statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"break.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/break.js b/break.js",
|
||||
"index 16ebcc57..629dfa91 100644",
|
||||
"--- a/break.js",
|
||||
"+++ b/break.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-for (i = 0; i < 10; i++) { if (i === 4) { continue; }; i }",
|
||||
"+for (i = 0; i < 10; i++) { if (i === 4) { break; }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "3bcd48f5d5894250de6349c4ca5272b3ae92fa6d..bbabc7d7ad65f9ab05f74f83c6e5777a3eeb4be2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-break-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"break.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
41
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
45
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the '{ }' object in the 'i === 4' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
49
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted a break statement in the 'i === 4' if statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"break.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/break.js b/break.js",
|
||||
"index 629dfa91..3f583e3d 100644",
|
||||
"--- a/break.js",
|
||||
"+++ b/break.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-for (i = 0; i < 10; i++) { if (i === 4) { break; }; i }",
|
||||
"+for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "bbabc7d7ad65f9ab05f74f83c6e5777a3eeb4be2..016996f57081dda9f5b4ebdd801853944017b617"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-break-teardown-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"break.js": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
50
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'i = 0; i < 10; i++' for statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"break.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/break.js b/break.js",
|
||||
"index 3f583e3d..e69de29b 100644",
|
||||
"--- a/break.js",
|
||||
"+++ b/break.js",
|
||||
"@@ -1 +0,0 @@",
|
||||
"-for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "016996f57081dda9f5b4ebdd801853944017b617..7b31459c5a9378f4fe26f4e3e6d5c1fd3b6aee23"
|
||||
}]
|
@ -16,7 +16,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'returned.promise().done(…).fail(…)' return statement"
|
||||
"summary": "Added the 'returned.promise().done( newDefer.resolve ).fail( newDefer.reject )' return statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -27,14 +27,14 @@
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/chained-property-access.js b/chained-property-access.js",
|
||||
"index e69de29..5914a55 100644",
|
||||
"index e69de29b..5914a55c 100644",
|
||||
"--- a/chained-property-access.js",
|
||||
"+++ b/chained-property-access.js",
|
||||
"@@ -0,0 +1 @@",
|
||||
"+return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "71feda9fd80ab60adab5cf81748710b2a610173f..02c42e637780aeb5874c5f740ba764a0b606d950"
|
||||
"shas": "b4a1b602905b005b1bfe48d8f78faebd8c9cf016..e4dd7ea96606956464809e9a3bcfdb81f318c39b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-replacement-insert-test",
|
||||
@ -54,7 +54,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'returned.promise().done(…).fail(…)' return statement"
|
||||
"summary": "Added the 'returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )' return statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -69,7 +69,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'returned.promise().done(…).fail(…)' return statement"
|
||||
"summary": "Added the 'returned.promise().done( newDefer.resolve ).fail( newDefer.reject )' return statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -80,7 +80,7 @@
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/chained-property-access.js b/chained-property-access.js",
|
||||
"index 5914a55..7095976 100644",
|
||||
"index 5914a55c..70959766 100644",
|
||||
"--- a/chained-property-access.js",
|
||||
"+++ b/chained-property-access.js",
|
||||
"@@ -1 +1,3 @@",
|
||||
@ -89,7 +89,7 @@
|
||||
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "02c42e637780aeb5874c5f740ba764a0b606d950..eb64ebf3bc9351da0d4cbb59cdfc44d7152b090e"
|
||||
"shas": "e4dd7ea96606956464809e9a3bcfdb81f318c39b..6365577e012aa898ba1d2cc77d10eec1fb9a016d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-delete-insert-test",
|
||||
@ -159,7 +159,7 @@
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/chained-property-access.js b/chained-property-access.js",
|
||||
"index 7095976..98df938 100644",
|
||||
"index 70959766..98df938b 100644",
|
||||
"--- a/chained-property-access.js",
|
||||
"+++ b/chained-property-access.js",
|
||||
"@@ -1,3 +1,3 @@",
|
||||
@ -169,7 +169,7 @@
|
||||
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "eb64ebf3bc9351da0d4cbb59cdfc44d7152b090e..d87ef7df3e23f3b4837c9dd09aeca869774aa731"
|
||||
"shas": "6365577e012aa898ba1d2cc77d10eec1fb9a016d..8ab9cd6c506847581b2fc7f04124803cd344b3ff"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-replacement-test",
|
||||
@ -239,7 +239,7 @@
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/chained-property-access.js b/chained-property-access.js",
|
||||
"index 98df938..7095976 100644",
|
||||
"index 98df938b..70959766 100644",
|
||||
"--- a/chained-property-access.js",
|
||||
"+++ b/chained-property-access.js",
|
||||
"@@ -1,3 +1,3 @@",
|
||||
@ -249,7 +249,7 @@
|
||||
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "d87ef7df3e23f3b4837c9dd09aeca869774aa731..2e00036e857c5aa6af0eb4ab23bd4cbb28bd90a2"
|
||||
"shas": "8ab9cd6c506847581b2fc7f04124803cd344b3ff..d535074522aa956a8ea7e8d943227d9d78775725"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-delete-replacement-test",
|
||||
@ -269,7 +269,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement"
|
||||
"summary": "Deleted the 'returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )' return statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -284,7 +284,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement"
|
||||
"summary": "Deleted the 'returned.promise().done( newDefer.resolve ).fail( newDefer.reject )' return statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -299,7 +299,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'returned.promise().done(…).fail(…)' return statement"
|
||||
"summary": "Added the 'returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )' return statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -310,7 +310,7 @@
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/chained-property-access.js b/chained-property-access.js",
|
||||
"index 7095976..7b764ca 100644",
|
||||
"index 70959766..7b764ca9 100644",
|
||||
"--- a/chained-property-access.js",
|
||||
"+++ b/chained-property-access.js",
|
||||
"@@ -1,3 +1,2 @@",
|
||||
@ -320,7 +320,7 @@
|
||||
"+return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "2e00036e857c5aa6af0eb4ab23bd4cbb28bd90a2..5eb335f13f0dea85c75b4d5f174832b08af8a0e6"
|
||||
"shas": "d535074522aa956a8ea7e8d943227d9d78775725..b3f90f50ba0ea4d42e78ba37c176a4d69282fcd7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-delete-test",
|
||||
@ -340,7 +340,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement"
|
||||
"summary": "Deleted the 'returned.promise().done( newDefer.resolve ).fail( newDefer.reject )' return statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -351,7 +351,7 @@
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/chained-property-access.js b/chained-property-access.js",
|
||||
"index 7b764ca..5d6d3a0 100644",
|
||||
"index 7b764ca9..5d6d3a02 100644",
|
||||
"--- a/chained-property-access.js",
|
||||
"+++ b/chained-property-access.js",
|
||||
"@@ -1,2 +1 @@",
|
||||
@ -359,7 +359,7 @@
|
||||
" return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "5eb335f13f0dea85c75b4d5f174832b08af8a0e6..054acb661f91e8a5b9096d552c5b3410bacc4811"
|
||||
"shas": "b3f90f50ba0ea4d42e78ba37c176a4d69282fcd7..6dd90e85a905d3c205cd42bcbedaa3d50110d426"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-delete-rest-test",
|
||||
@ -379,7 +379,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement"
|
||||
"summary": "Deleted the 'returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )' return statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -390,12 +390,12 @@
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/chained-property-access.js b/chained-property-access.js",
|
||||
"index 5d6d3a0..e69de29 100644",
|
||||
"index 5d6d3a02..e69de29b 100644",
|
||||
"--- a/chained-property-access.js",
|
||||
"+++ b/chained-property-access.js",
|
||||
"@@ -1 +0,0 @@",
|
||||
"-return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "054acb661f91e8a5b9096d552c5b3410bacc4811..1512ae1cef2a096ce2723ce98334e4ce0e4bc82b"
|
||||
"shas": "6dd90e85a905d3c205cd42bcbedaa3d50110d426..7b26c97829302e6f2c2fc76d9a1e5dc25caf58d9"
|
||||
}]
|
||||
|
292
test/corpus/diff-summaries/javascript/continue.json
Normal file
292
test/corpus/diff-summaries/javascript/continue.json
Normal file
@ -0,0 +1,292 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-continue-setup-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"continue.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
50
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'i = 0; i < 10; i++' for statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"continue.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/continue.js b/continue.js",
|
||||
"index e69de29b..3f583e3d 100644",
|
||||
"--- a/continue.js",
|
||||
"+++ b/continue.js",
|
||||
"@@ -0,0 +1 @@",
|
||||
"+for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "7b31459c5a9378f4fe26f4e3e6d5c1fd3b6aee23..6f1f37c267e2d029c289f0fbcf27091ba3d1dec0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-continue-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"continue.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
52
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added a continue statement in the 'i === 4' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
41
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
45
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the '{ }' object in the 'i === 4' if statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"continue.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/continue.js b/continue.js",
|
||||
"index 3f583e3d..16ebcc57 100644",
|
||||
"--- a/continue.js",
|
||||
"+++ b/continue.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-for (i = 0; i < 10; i++) { if (i === 4) { }; i }",
|
||||
"+for (i = 0; i < 10; i++) { if (i === 4) { continue; }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "6f1f37c267e2d029c289f0fbcf27091ba3d1dec0..b23c299b2611ac212c2f335a44e9ffcfbe821ed4"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-continue-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"continue.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
49
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added a break statement in the 'i === 4' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
52
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted a continue statement in the 'i === 4' if statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"continue.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/continue.js b/continue.js",
|
||||
"index 16ebcc57..629dfa91 100644",
|
||||
"--- a/continue.js",
|
||||
"+++ b/continue.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-for (i = 0; i < 10; i++) { if (i === 4) { continue; }; i }",
|
||||
"+for (i = 0; i < 10; i++) { if (i === 4) { break; }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "b23c299b2611ac212c2f335a44e9ffcfbe821ed4..59f5084383702801c670c2d9738a4d78c93a0b0a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-continue-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"continue.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
52
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added a continue statement in the 'i === 4' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
49
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted a break statement in the 'i === 4' if statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"continue.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/continue.js b/continue.js",
|
||||
"index 629dfa91..16ebcc57 100644",
|
||||
"--- a/continue.js",
|
||||
"+++ b/continue.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-for (i = 0; i < 10; i++) { if (i === 4) { break; }; i }",
|
||||
"+for (i = 0; i < 10; i++) { if (i === 4) { continue; }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "59f5084383702801c670c2d9738a4d78c93a0b0a..ac045f406aaa05c9c85d6a20e527e2e62e99ce2c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-continue-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"continue.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
41
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
45
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the '{ }' object in the 'i === 4' if statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
43
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
52
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted a continue statement in the 'i === 4' if statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"continue.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/continue.js b/continue.js",
|
||||
"index 16ebcc57..3f583e3d 100644",
|
||||
"--- a/continue.js",
|
||||
"+++ b/continue.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-for (i = 0; i < 10; i++) { if (i === 4) { continue; }; i }",
|
||||
"+for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "ac045f406aaa05c9c85d6a20e527e2e62e99ce2c..0c96f2e07ccf5ac404d4301a1a1e5ca9aa19b0b3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-continue-teardown-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"continue.js": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
50
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'i = 0; i < 10; i++' for statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"continue.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/continue.js b/continue.js",
|
||||
"index 3f583e3d..e69de29b 100644",
|
||||
"--- a/continue.js",
|
||||
"+++ b/continue.js",
|
||||
"@@ -1 +0,0 @@",
|
||||
"-for (i = 0; i < 10; i++) { if (i === 4) { }; i }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "0c96f2e07ccf5ac404d4301a1a1e5ca9aa19b0b3..b4a1b602905b005b1bfe48d8f78faebd8c9cf016"
|
||||
}]
|
@ -54,7 +54,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'empty' return statement"
|
||||
"summary": "Added a return statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -191,7 +191,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'empty' return statement"
|
||||
"summary": "Deleted a return statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -221,7 +221,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'empty' return statement"
|
||||
"summary": "Added a return statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -301,7 +301,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'empty' return statement"
|
||||
"summary": "Deleted a return statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
|
256
test/corpus/diff-summaries/javascript/yield.json
Normal file
256
test/corpus/diff-summaries/javascript/yield.json
Normal file
@ -0,0 +1,256 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-yield-setup-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"yield.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
35
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'foo' function"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"yield.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/yield.js b/yield.js",
|
||||
"index e69de29b..e01b17c7 100644",
|
||||
"--- a/yield.js",
|
||||
"+++ b/yield.js",
|
||||
"@@ -0,0 +1 @@",
|
||||
"+function* foo(){ var index = 0; }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "5c6bdce8f72c2d775feff2e1e2bafd6639ec3092..af359d80f0450c0c2196373f3a6135ad69d15448"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-yield-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"yield.js": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
33
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
41
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'i' yield statement in the foo function"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"yield.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/yield.js b/yield.js",
|
||||
"index e01b17c7..e2088166 100644",
|
||||
"--- a/yield.js",
|
||||
"+++ b/yield.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-function* foo(){ var index = 0; }",
|
||||
"+function* foo(){ var index = 0; yield i; }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "af359d80f0450c0c2196373f3a6135ad69d15448..994d3630d7493bcd3de8987ef154ab8791944584"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-yield-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"yield.js": [
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
33
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
41
|
||||
]
|
||||
},
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
33
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
43
|
||||
]
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'i' yield statement with the 'i++' yield statement in the foo function"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"yield.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/yield.js b/yield.js",
|
||||
"index e2088166..78ab2efe 100644",
|
||||
"--- a/yield.js",
|
||||
"+++ b/yield.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-function* foo(){ var index = 0; yield i; }",
|
||||
"+function* foo(){ var index = 0; yield i++; }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "994d3630d7493bcd3de8987ef154ab8791944584..04b9b20aaf2b5f555b5223dfba6c303f01450f5e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-yield-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"yield.js": [
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
33
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
43
|
||||
]
|
||||
},
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
33
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
41
|
||||
]
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'i++' yield statement with the 'i' yield statement in the foo function"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"yield.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/yield.js b/yield.js",
|
||||
"index 78ab2efe..e2088166 100644",
|
||||
"--- a/yield.js",
|
||||
"+++ b/yield.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-function* foo(){ var index = 0; yield i++; }",
|
||||
"+function* foo(){ var index = 0; yield i; }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "04b9b20aaf2b5f555b5223dfba6c303f01450f5e..0f042b1a2b628149d5fe3d38ac22ddb0b1e1fd4a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-yield-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"yield.js": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
33
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
41
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'i' yield statement in the foo function"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"yield.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/yield.js b/yield.js",
|
||||
"index e2088166..e01b17c7 100644",
|
||||
"--- a/yield.js",
|
||||
"+++ b/yield.js",
|
||||
"@@ -1 +1 @@",
|
||||
"-function* foo(){ var index = 0; yield i; }",
|
||||
"+function* foo(){ var index = 0; }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "0f042b1a2b628149d5fe3d38ac22ddb0b1e1fd4a..2bb888580d4105d265e9137474d813ab92ce6359"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-yield-teardown-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"yield.js": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
35
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'foo' function"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"yield.js"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/yield.js b/yield.js",
|
||||
"index e01b17c7..e69de29b 100644",
|
||||
"--- a/yield.js",
|
||||
"+++ b/yield.js",
|
||||
"@@ -1 +0,0 @@",
|
||||
"-function* foo(){ var index = 0; }"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"shas": "2bb888580d4105d265e9137474d813ab92ce6359..0e81c586bea55e0eeb46e3422b25ccba96c7d9ea"
|
||||
}]
|
@ -34,7 +34,7 @@
|
||||
"+return foo"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "b9eed5bd1eb6aacf2a54e334b4297955018776a8..bea7290ff72c82de8db2a0c9ae8eae0095f9f133"
|
||||
"shas": "c098817a0924917fa730442b5593361c7558bf94..d177fc3b7a364cc0c0f9b99a698f8368dee22c8c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-return-replacement-insert-test",
|
||||
@ -54,7 +54,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'empty' return statement"
|
||||
"summary": "Added a return statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -89,7 +89,7 @@
|
||||
" return foo"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "bea7290ff72c82de8db2a0c9ae8eae0095f9f133..328345c3ed837afd421202db539c4e8b374e4877"
|
||||
"shas": "d177fc3b7a364cc0c0f9b99a698f8368dee22c8c..53ea66673eb285331f75ac06d498cf043fc6c72b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-return-delete-insert-test",
|
||||
@ -130,7 +130,7 @@
|
||||
" return foo"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "328345c3ed837afd421202db539c4e8b374e4877..564f0138ad63d31ca573e410cd1f69143df79e04"
|
||||
"shas": "53ea66673eb285331f75ac06d498cf043fc6c72b..d608622f26473010fc66350571ca61c49fc2fe22"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-return-replacement-test",
|
||||
@ -171,7 +171,7 @@
|
||||
" return foo"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "564f0138ad63d31ca573e410cd1f69143df79e04..daf6b77e4ee816ceef89bc43e56baa339ca2708f"
|
||||
"shas": "d608622f26473010fc66350571ca61c49fc2fe22..3ac4d31eb749e7ad1387372ebec9a2e6b84a63e3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-return-delete-replacement-test",
|
||||
@ -191,7 +191,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'empty' return statement"
|
||||
"summary": "Deleted a return statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -221,7 +221,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'empty' return statement"
|
||||
"summary": "Added a return statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -242,7 +242,7 @@
|
||||
"+return"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "daf6b77e4ee816ceef89bc43e56baa339ca2708f..837ad22ea13472d087a09e873830453c9e7bf89d"
|
||||
"shas": "3ac4d31eb749e7ad1387372ebec9a2e6b84a63e3..4beff4220223e005a178c4d68b23b32b3a1ecd48"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-return-delete-test",
|
||||
@ -281,7 +281,7 @@
|
||||
" return"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "837ad22ea13472d087a09e873830453c9e7bf89d..76fdd8535cd04dcae0eef2cddafc74d3176932f6"
|
||||
"shas": "4beff4220223e005a178c4d68b23b32b3a1ecd48..1428f73c2494d079bf29b577b69da0f668d36be1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-return-delete-rest-test",
|
||||
@ -301,7 +301,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'empty' return statement"
|
||||
"summary": "Deleted a return statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -319,5 +319,5 @@
|
||||
"-return"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "76fdd8535cd04dcae0eef2cddafc74d3176932f6..e9e47a7e8dfaea6fade11176891263b27322f29d"
|
||||
"shas": "1428f73c2494d079bf29b577b69da0f668d36be1..6320f83c8822c0efc1ee3f921342eb41977e9fb8"
|
||||
}]
|
||||
|
@ -54,7 +54,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'empty' yield statement"
|
||||
"summary": "Added a yield statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -191,7 +191,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'empty' yield statement"
|
||||
"summary": "Deleted a yield statement"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
@ -221,7 +221,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'empty' yield statement"
|
||||
"summary": "Added a yield statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -301,7 +301,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'empty' yield statement"
|
||||
"summary": "Deleted a yield statement"
|
||||
}
|
||||
]
|
||||
},
|
||||
|
@ -308,6 +308,24 @@
|
||||
"syntax": "export",
|
||||
"insert": "export { name1, name2, name3, nameN };\nexport { variable1 as name1, variable2 as name2, nameN };\nexport let name1, name2, nameN;\nexport let name1 = value1, name2 = value2, name3, nameN;\nexport default namedFunction;\nexport default function () { };\nexport default function name1() { };\nexport { name1 as default };\nexport * from 'foo';\nexport { name1, name2, nameN } from 'foo';\nexport { import1 as name1, import2 as name2, nameN } from 'bar';",
|
||||
"replacement": "export { name4, name5, name6, nameZ };\nexport { variable2 as name2, variable3 as name3, nameY };\nexport let name3, name4, nameT;\nexport let name2 = value2, name3 = value3, name4, nameO;\nexport default otherNamedFunction;\nexport default function newName1() {};\nexport default function () {};\nexport { name2 as statement };\nexport * from 'baz';\nexport { name7, name8, nameP } from 'buzz';\nexport { import6 as name6, import7 as name7, nameB } from 'fizz';"
|
||||
},
|
||||
{
|
||||
"syntax": "break",
|
||||
"insert": "break;",
|
||||
"replacement": "continue;",
|
||||
"template": "for (i = 0; i < 10; i++) { if (i === 4) { {0} }; i }"
|
||||
},
|
||||
{
|
||||
"syntax": "continue",
|
||||
"insert": "continue;",
|
||||
"replacement": "break;",
|
||||
"template": "for (i = 0; i < 10; i++) { if (i === 4) { {0} }; i }"
|
||||
},
|
||||
{
|
||||
"syntax": "yield",
|
||||
"insert": "yield i;",
|
||||
"replacement": "yield i++;",
|
||||
"template": "function* foo(){ var index = 0; {0} }"
|
||||
}
|
||||
]
|
||||
}
|
||||
|
@ -1,14 +0,0 @@
|
||||
[
|
||||
{
|
||||
"language": "javascript",
|
||||
"fileExt": ".js",
|
||||
"repoUrl": "https://github.com/diff-fixtures/javascript.git",
|
||||
"syntaxes": [
|
||||
{
|
||||
"syntax": "object",
|
||||
"insert": "{ \"key1\": \"value1\" };",
|
||||
"replacement": "{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };"
|
||||
}
|
||||
]
|
||||
}
|
||||
]
|
@ -1,14 +0,0 @@
|
||||
[
|
||||
{
|
||||
"language": "ruby",
|
||||
"fileExt": ".rb",
|
||||
"repoUrl": "https://github.com/diff-fixtures/ruby.git",
|
||||
"syntaxes": [
|
||||
{
|
||||
"syntax": "hash",
|
||||
"insert": "{ :key1 => \"value\", :key2 => 1, \"key3\" => false, :\"symbol_key\" => 10 }",
|
||||
"replacement": "{ key1: \"changed value\", key2: 2, key3: true }"
|
||||
}
|
||||
]
|
||||
}
|
||||
]
|
@ -1 +1 @@
|
||||
Subproject commit 9a8e607838c835f05173da887153445f52079f01
|
||||
Subproject commit 5e49cf8bc49a6acceee67258f44392614d3e2807
|
@ -1 +1 @@
|
||||
Subproject commit ba01e3794a8efa31353fd2d5726c70bb2ad8c6a8
|
||||
Subproject commit 7b26c97829302e6f2c2fc76d9a1e5dc25caf58d9
|
@ -1 +1 @@
|
||||
Subproject commit a8b440ad76232e4e95f5a5ed53b9b6604ece8a17
|
||||
Subproject commit 6320f83c8822c0efc1ee3f921342eb41977e9fb8
|
2
vendor/tree-sitter-parsers
vendored
2
vendor/tree-sitter-parsers
vendored
@ -1 +1 @@
|
||||
Subproject commit 4059323af986c544171eaed0a84adedb239d174b
|
||||
Subproject commit 2664b1599b1e68f772d59aa0d41638cdaa2b7fbf
|
Loading…
Reference in New Issue
Block a user