mirror of
https://github.com/github/semantic.git
synced 2024-12-01 09:15:01 +03:00
Merge remote-tracking branch 'origin/master' into cache-and-discard-feature-vectors
This commit is contained in:
commit
398bb62d16
2
languages/ruby/vendor/tree-sitter-ruby
vendored
2
languages/ruby/vendor/tree-sitter-ruby
vendored
@ -1 +1 @@
|
||||
Subproject commit 5f71c72bb45586811436a4c3d2e3da12e3009283
|
||||
Subproject commit b2ca35ffc5b1e3eec5ee41fc3d0420788dffa04a
|
@ -18,6 +18,7 @@ module Data.Functor.Listable
|
||||
, liftCons2
|
||||
, liftCons3
|
||||
, liftCons4
|
||||
, liftCons5
|
||||
, ListableF(..)
|
||||
) where
|
||||
|
||||
@ -74,6 +75,13 @@ liftCons4 :: [Tier a] -> [Tier b] -> [Tier c] -> [Tier d] -> (a -> b -> c -> d -
|
||||
liftCons4 tiers1 tiers2 tiers3 tiers4 f = mapT (uncurry4 f) (productWith (\ x (y, z, w) -> (x, y, z, w)) tiers1 (liftCons3 tiers2 tiers3 tiers4 (,,)) ) `addWeight` 1
|
||||
where uncurry4 f (a, b, c, d) = f a b c d
|
||||
|
||||
-- | Lifts a quinary constructor to a list of tiers, given lists of tiers for its arguments.
|
||||
--
|
||||
-- Commonly used in the definition of 'Listable1' and 'Listable2' instances.
|
||||
liftCons5 :: [Tier a] -> [Tier b] -> [Tier c] -> [Tier d] -> [Tier e] -> (a -> b -> c -> d -> e -> f) -> [Tier f]
|
||||
liftCons5 tiers1 tiers2 tiers3 tiers4 tiers5 f = mapT (uncurry5 f) (productWith (\ x (y, z, w, u) -> (x, y, z, w, u)) tiers1 (liftCons4 tiers2 tiers3 tiers4 tiers5 (,,,)) ) `addWeight` 1
|
||||
where uncurry5 f (a, b, c, d, e) = f a b c d e
|
||||
|
||||
-- | Convenient wrapper for 'Listable1' type constructors and 'Listable' types, where a 'Listable' instance would necessarily be orphaned.
|
||||
newtype ListableF f a = ListableF { unListableF :: f a }
|
||||
deriving Show
|
||||
|
@ -251,7 +251,8 @@ toTermName source term = case unwrap term of
|
||||
S.Select clauses -> termNameFromChildren term clauses
|
||||
S.Array ty _ -> maybe (termNameFromSource term) termNameFromSource ty
|
||||
S.Class identifier _ _ -> toTermName' identifier
|
||||
S.Method identifier _ args _ -> toTermName' identifier <> paramsToArgNames args
|
||||
S.Method identifier (Just receiver) _ args _ -> termNameFromSource receiver <> "." <> toTermName' identifier <> paramsToArgNames args
|
||||
S.Method identifier Nothing _ args _ -> toTermName' identifier <> paramsToArgNames args
|
||||
S.Comment a -> toS a
|
||||
S.Commented _ _ -> termNameFromChildren term (toList $ unwrap term)
|
||||
S.Module identifier _ -> toTermName' identifier
|
||||
|
@ -76,8 +76,9 @@ algorithmWithTerms construct t1 t2 = maybe (recursively t1 t2) (fmap annotate) $
|
||||
S.Class <$> recursively identifierA identifierB
|
||||
<*> maybeRecursively paramsA paramsB
|
||||
<*> bySimilarity expressionsA expressionsB
|
||||
(S.Method identifierA tyA paramsA expressionsA, S.Method identifierB tyB paramsB expressionsB) -> Just $
|
||||
(S.Method identifierA receiverA tyA paramsA expressionsA, S.Method identifierB receiverB tyB paramsB expressionsB) -> Just $
|
||||
S.Method <$> recursively identifierA identifierB
|
||||
<*> maybeRecursively receiverA receiverB
|
||||
<*> maybeRecursively tyA tyB
|
||||
<*> bySimilarity paramsA paramsB
|
||||
<*> bySimilarity expressionsA expressionsB
|
||||
|
@ -65,12 +65,14 @@ termAssignment source category children = case (category, children) of
|
||||
(Send, [channel, expr]) -> Just $ S.Send channel expr
|
||||
(Operator, _) -> Just $ S.Operator children
|
||||
(FunctionTy, _) -> Just $ S.Ty children
|
||||
(IncrementStatement, _) -> Just $ S.Leaf $ toText source
|
||||
(DecrementStatement, _) -> Just $ S.Leaf $ toText source
|
||||
(QualifiedIdentifier, _) -> Just $ S.Leaf $ toText source
|
||||
(Method, [params, name, fun]) -> Just (S.Method name Nothing (toList (unwrap params)) (toList (unwrap fun)))
|
||||
(Method, [params, name, outParams, fun]) -> Just (S.Method name Nothing (toList (unwrap params) <> toList (unwrap outParams)) (toList (unwrap fun)))
|
||||
(Method, [params, name, outParams, ty, fun]) -> Just (S.Method name (Just ty) (toList (unwrap params) <> toList (unwrap outParams)) (toList (unwrap fun)))
|
||||
(IncrementStatement, _) -> Just $ S.Leaf (toText source)
|
||||
(DecrementStatement, _) -> Just $ S.Leaf (toText source)
|
||||
(QualifiedIdentifier, _) -> Just $ S.Leaf (toText source)
|
||||
(Method, [params, name, fun]) -> Just (S.Method name Nothing Nothing (toList (unwrap params)) (toList (unwrap fun)))
|
||||
(Method, [params, name, outParams, fun])
|
||||
-> Just (S.Method name (Just outParams) Nothing (toList (unwrap params)) (toList (unwrap fun)))
|
||||
(Method, [params, name, outParams, ty, fun])
|
||||
-> Just (S.Method name (Just outParams) (Just ty) (toList (unwrap params)) (toList (unwrap fun)))
|
||||
_ -> Nothing
|
||||
|
||||
categoryForGoName :: Text -> Category
|
||||
|
@ -44,8 +44,8 @@ termAssignment _ category children
|
||||
, Finally <- Info.category (extract finally)
|
||||
-> Just $ S.Try [body] [catch] Nothing (Just finally)
|
||||
(ArrayLiteral, _) -> Just $ S.Array Nothing children
|
||||
(Method, [ identifier, params, exprs ]) -> Just $ S.Method identifier Nothing (toList (unwrap params)) (toList (unwrap exprs))
|
||||
(Method, [ identifier, exprs ]) -> Just $ S.Method identifier Nothing [] (toList (unwrap exprs))
|
||||
(Method, [ identifier, params, exprs ]) -> Just $ S.Method identifier Nothing Nothing (toList (unwrap params)) (toList (unwrap exprs))
|
||||
(Method, [ identifier, exprs ]) -> Just $ S.Method identifier Nothing Nothing [] (toList (unwrap exprs))
|
||||
(Class, [ identifier, superclass, definitions ]) -> Just $ S.Class identifier (Just superclass) (toList (unwrap definitions))
|
||||
(Class, [ identifier, definitions ]) -> Just $ S.Class identifier Nothing (toList (unwrap definitions))
|
||||
(Import, [ statements, identifier ] ) -> Just $ S.Import identifier (toList (unwrap statements))
|
||||
|
@ -65,12 +65,18 @@ termAssignment _ category children
|
||||
(For, lhs : expr : rest ) -> Just $ S.For [lhs, expr] rest
|
||||
(OperatorAssignment, [ identifier, value ]) -> Just $ S.OperatorAssignment identifier value
|
||||
(MemberAccess, [ base, property ]) -> Just $ S.MemberAccess base property
|
||||
(Method, expr : methodName : rest)
|
||||
| params : body <- rest
|
||||
, Params <- Info.category (extract params)
|
||||
-> Just $ S.Method methodName (Just expr) Nothing (toList (unwrap params)) body
|
||||
| Identifier <- Info.category (extract methodName)
|
||||
-> Just $ S.Method methodName (Just expr) Nothing [] rest
|
||||
(Method, identifier : rest)
|
||||
| params : body <- rest
|
||||
, Params <- Info.category (extract params)
|
||||
-> Just $ S.Method identifier Nothing (toList (unwrap params)) body
|
||||
-> Just $ S.Method identifier Nothing Nothing (toList (unwrap params)) body
|
||||
| otherwise
|
||||
-> Just $ S.Method identifier Nothing [] rest
|
||||
-> Just $ S.Method identifier Nothing Nothing [] rest
|
||||
(Module, constant : body ) -> Just $ S.Module constant body
|
||||
(Modifier Rescue, [lhs, rhs] ) -> Just $ S.Rescue [lhs] [rhs]
|
||||
(Rescue, exceptions : exceptionVar : rest)
|
||||
@ -93,6 +99,7 @@ termAssignment _ category children
|
||||
categoryForRubyName :: Text -> Category
|
||||
categoryForRubyName = \case
|
||||
"argument_list" -> Args
|
||||
"argument_list_with_parens" -> Args
|
||||
"argument_pair" -> ArgumentPair
|
||||
"array" -> ArrayLiteral
|
||||
"assignment" -> Assignment
|
||||
@ -100,6 +107,7 @@ categoryForRubyName = \case
|
||||
"begin" -> Begin
|
||||
"binary" -> Binary
|
||||
"block_parameter" -> BlockParameter
|
||||
"block_parameters" -> Params
|
||||
"boolean" -> Boolean
|
||||
"call" -> MemberAccess
|
||||
"case" -> Case
|
||||
@ -110,6 +118,7 @@ categoryForRubyName = \case
|
||||
"element_reference" -> SubscriptAccess
|
||||
"else" -> Else
|
||||
"elsif" -> Elsif
|
||||
"empty_statement" -> Empty
|
||||
"end_block" -> EndBlock
|
||||
"ensure" -> Ensure
|
||||
"exception_variable" -> RescuedException
|
||||
@ -117,9 +126,6 @@ categoryForRubyName = \case
|
||||
"false" -> Boolean
|
||||
"float" -> NumberLiteral
|
||||
"for" -> For
|
||||
"method_parameters" -> Params
|
||||
"lambda_parameters" -> Params
|
||||
"block_parameters" -> Params
|
||||
"hash_splat_parameter" -> HashSplatParameter
|
||||
"hash" -> Object
|
||||
"identifier" -> Identifier
|
||||
@ -129,7 +135,9 @@ categoryForRubyName = \case
|
||||
"integer" -> IntegerLiteral
|
||||
"interpolation" -> Interpolation
|
||||
"keyword_parameter" -> KeywordParameter
|
||||
"lambda_parameters" -> Params
|
||||
"method_call" -> MethodCall
|
||||
"method_parameters" -> Params
|
||||
"method" -> Method
|
||||
"module" -> Module
|
||||
"nil" -> Identifier
|
||||
|
@ -129,7 +129,7 @@ syntaxToTermField syntax = case syntax of
|
||||
S.Try body catchExpression elseExpression finallyExpression -> [ "body" .= body ] <> [ "catchExpression" .= catchExpression ] <> [ "elseExpression" .= elseExpression ] <> [ "finallyExpression" .= finallyExpression ]
|
||||
S.Array ty c -> [ "type" .= ty ] <> childrenFields c
|
||||
S.Class identifier superclass definitions -> [ "identifier" .= identifier ] <> [ "superclass" .= superclass ] <> [ "definitions" .= definitions ]
|
||||
S.Method identifier ty parameters definitions -> [ "identifier" .= identifier ] <> [ "type" .= ty ] <> [ "parameters" .= parameters ] <> [ "definitions" .= definitions ]
|
||||
S.Method identifier receiver ty parameters definitions -> [ "identifier" .= identifier ] <> [ "receiver" .= receiver ] <> [ "type" .= ty ] <> [ "parameters" .= parameters ] <> [ "definitions" .= definitions ]
|
||||
S.If expression clauses -> [ "expression" .= expression ] <> childrenFields clauses
|
||||
S.Module identifier definitions-> [ "identifier" .= identifier ] <> [ "definitions" .= definitions ]
|
||||
S.Import identifier statements -> [ "identifier" .= identifier ] <> [ "statements" .= statements ]
|
||||
|
@ -152,7 +152,8 @@ termToDiffInfo blob term = case unwrap term of
|
||||
toTermName :: forall leaf fields. DefaultFields fields => Source Char -> SyntaxTerm leaf fields -> Text
|
||||
toTermName source term = case unwrap term of
|
||||
S.Function identifier _ _ _ -> toTermName' identifier
|
||||
S.Method identifier _ _ _ -> toTermName' identifier
|
||||
S.Method identifier Nothing _ _ _ -> toTermName' identifier
|
||||
S.Method identifier (Just receiver) _ _ _ -> toTermName' receiver <> "." <> toTermName' identifier
|
||||
_ -> termNameFromSource term
|
||||
where
|
||||
toTermName' = toTermName source
|
||||
|
@ -71,8 +71,8 @@ data Syntax a f
|
||||
| Array (Maybe f) [f]
|
||||
-- | A class with an identifier, superclass, and a list of definitions.
|
||||
| Class f (Maybe f) [f]
|
||||
-- | A method definition with an identifier, optional return type, params, and a list of expressions.
|
||||
| Method f (Maybe f) [f] [f]
|
||||
-- | A method definition with an identifier, optional receiver, optional return type, params, and a list of expressions.
|
||||
| Method f (Maybe f) (Maybe f) [f] [f]
|
||||
-- | An if statement with an expression and maybe more expression clauses.
|
||||
| If f [f]
|
||||
-- | A module with an identifier, and a list of syntaxes.
|
||||
@ -143,7 +143,7 @@ instance Listable2 Syntax where
|
||||
\/ liftCons4 (liftTiers recur) (liftTiers recur) (liftTiers recur) (liftTiers recur) Try
|
||||
\/ liftCons2 (liftTiers recur) (liftTiers recur) Syntax.Array
|
||||
\/ liftCons3 recur (liftTiers recur) (liftTiers recur) Class
|
||||
\/ liftCons4 recur (liftTiers recur) (liftTiers recur) (liftTiers recur) Method
|
||||
\/ liftCons5 recur (liftTiers recur) (liftTiers recur) (liftTiers recur) (liftTiers recur) Method
|
||||
\/ liftCons2 recur (liftTiers recur) If
|
||||
\/ liftCons2 recur (liftTiers recur) Module
|
||||
\/ liftCons2 recur (liftTiers recur) Import
|
||||
|
@ -53,7 +53,7 @@
|
||||
"+"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "d6222a7346773adfd0929112bedb22129a3519ea..e6c36e250ec3b19c41f32961ccebf3d87daedda7"
|
||||
"shas": "177fb35939c02b4bc6067142eab57a6cc2237513..2f023a586a3c306c01e1fbf646c7bffc5a6428b3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-method-declarations-insert-test",
|
||||
@ -73,7 +73,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'Equals(…, …)' method"
|
||||
"summary": "Added the '(other Person).Equals(…)' method"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -95,40 +95,13 @@
|
||||
"+func (self Person) Equals(other Person) bool {}"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "e6c36e250ec3b19c41f32961ccebf3d87daedda7..8997e3526ed2c41b2dcdda92e804efb3877995b7"
|
||||
"shas": "2f023a586a3c306c01e1fbf646c7bffc5a6428b3..d79d8d6400fbf0ee98ec1c1de105b35653bc6abf"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-method-declarations-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-declarations.go": [
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
{
|
||||
"start": [
|
||||
5,
|
||||
12
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
18
|
||||
]
|
||||
},
|
||||
{
|
||||
"start": [
|
||||
5,
|
||||
12
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
15
|
||||
]
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'Person' identifier with the 'Num' identifier in the 'Equals(…, …)' method"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
@ -154,7 +127,34 @@
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'Person' identifier with the 'Num' identifier in the 'Equals(…, …)' method"
|
||||
"summary": "Replaced the 'Person' identifier with the 'Num' identifier in the '(other Num).Equals(…)' method"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
{
|
||||
"start": [
|
||||
5,
|
||||
12
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
18
|
||||
]
|
||||
},
|
||||
{
|
||||
"start": [
|
||||
5,
|
||||
12
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
15
|
||||
]
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'Person' identifier with the 'Num' identifier in the '(other Num).Equals(…)' method"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -176,40 +176,13 @@
|
||||
"+func (self Num) Equals(other Num) bool {}"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "8997e3526ed2c41b2dcdda92e804efb3877995b7..f08fde8bdfc53bd37c4432795460d589a75095aa"
|
||||
"shas": "d79d8d6400fbf0ee98ec1c1de105b35653bc6abf..4984840b9c1f873e4f0283f9aa56578524bc318a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-method-declarations-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-declarations.go": [
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
{
|
||||
"start": [
|
||||
5,
|
||||
12
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
15
|
||||
]
|
||||
},
|
||||
{
|
||||
"start": [
|
||||
5,
|
||||
12
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
18
|
||||
]
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'Num' identifier with the 'Person' identifier in the 'Equals(…, …)' method"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
@ -235,7 +208,34 @@
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'Num' identifier with the 'Person' identifier in the 'Equals(…, …)' method"
|
||||
"summary": "Replaced the 'Num' identifier with the 'Person' identifier in the '(other Person).Equals(…)' method"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
{
|
||||
"start": [
|
||||
5,
|
||||
12
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
15
|
||||
]
|
||||
},
|
||||
{
|
||||
"start": [
|
||||
5,
|
||||
12
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
18
|
||||
]
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'Num' identifier with the 'Person' identifier in the '(other Person).Equals(…)' method"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -257,7 +257,7 @@
|
||||
"+func (self Person) Equals(other Person) bool {}"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "f08fde8bdfc53bd37c4432795460d589a75095aa..6894b07b35002c287e007ee22d368fc3ae5de4f3"
|
||||
"shas": "4984840b9c1f873e4f0283f9aa56578524bc318a..5d97f8471206dc97ee31629ea3a5513e44182603"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-method-declarations-delete-insert-test",
|
||||
@ -277,7 +277,7 @@
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'Equals(…, …)' method"
|
||||
"summary": "Deleted the '(other Person).Equals(…)' method"
|
||||
}
|
||||
]
|
||||
},
|
||||
@ -299,7 +299,7 @@
|
||||
"+"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "6894b07b35002c287e007ee22d368fc3ae5de4f3..36a54e70abf58b31b21f318fe98685a08ef1949f"
|
||||
"shas": "5d97f8471206dc97ee31629ea3a5513e44182603..e3c6f620532caea3d241a47bbaa17701dba91928"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "go-method-declarations-teardown-test",
|
||||
@ -356,5 +356,5 @@
|
||||
"-"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/go",
|
||||
"shas": "36a54e70abf58b31b21f318fe98685a08ef1949f..957e7a284d3bbaebd707764ceac202343581ccdb"
|
||||
"shas": "e3c6f620532caea3d241a47bbaa17701dba91928..852d29d2b9a695875dd0e15454330bbf7c5e49ff"
|
||||
}]
|
||||
|
@ -0,0 +1,426 @@
|
||||
[{
|
||||
"testCaseDescription": "ruby-singleton-method-declaration-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"singleton-method-declaration.rb": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
4
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'self.foo()' method"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"singleton-method-declaration.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/singleton-method-declaration.rb b/singleton-method-declaration.rb",
|
||||
"index e69de29..caaf49d 100644",
|
||||
"--- a/singleton-method-declaration.rb",
|
||||
"+++ b/singleton-method-declaration.rb",
|
||||
"@@ -0,0 +1,2 @@",
|
||||
"+def self.foo",
|
||||
"+end"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "dc8f828fb183ed9f9c1e6bc2225fc072ba04d16b..7ec5ddaad7ca5c2617b47286e6dd01154f0864ea"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-singleton-method-declaration-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"singleton-method-declaration.rb": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
3,
|
||||
4
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'self.bar(a)' method"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
4,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
4
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'self.foo()' method"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"singleton-method-declaration.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/singleton-method-declaration.rb b/singleton-method-declaration.rb",
|
||||
"index caaf49d..2393b4c 100644",
|
||||
"--- a/singleton-method-declaration.rb",
|
||||
"+++ b/singleton-method-declaration.rb",
|
||||
"@@ -1,2 +1,7 @@",
|
||||
"+def self.bar(a)",
|
||||
"+ baz",
|
||||
"+end",
|
||||
"+def self.foo",
|
||||
"+end",
|
||||
" def self.foo",
|
||||
" end"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "7ec5ddaad7ca5c2617b47286e6dd01154f0864ea..d5dd261daf5f486d25bfdc4be255aad96bcff349"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-singleton-method-declaration-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"singleton-method-declaration.rb": [
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
10
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
13
|
||||
]
|
||||
},
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
10
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
13
|
||||
]
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'bar' identifier with the 'foo' identifier in the 'self.foo()' method"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
14
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
15
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'a' identifier in the 'self.foo()' method"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
2,
|
||||
3
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
6
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'baz' identifier in the 'self.foo()' method"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"singleton-method-declaration.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/singleton-method-declaration.rb b/singleton-method-declaration.rb",
|
||||
"index 2393b4c..44b0e0c 100644",
|
||||
"--- a/singleton-method-declaration.rb",
|
||||
"+++ b/singleton-method-declaration.rb",
|
||||
"@@ -1,5 +1,4 @@",
|
||||
"-def self.bar(a)",
|
||||
"- baz",
|
||||
"+def self.foo",
|
||||
" end",
|
||||
" def self.foo",
|
||||
" end"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "d5dd261daf5f486d25bfdc4be255aad96bcff349..9be301df5bd043c27ece14f9ea370518be524a3b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-singleton-method-declaration-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"singleton-method-declaration.rb": [
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
10
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
13
|
||||
]
|
||||
},
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
10
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
13
|
||||
]
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the 'foo' identifier with the 'bar' identifier in the 'self.bar(a)' method"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
14
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
15
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'a' identifier in the 'self.bar(a)' method"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
2,
|
||||
3
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
6
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'baz' identifier in the 'self.bar(a)' method"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"singleton-method-declaration.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/singleton-method-declaration.rb b/singleton-method-declaration.rb",
|
||||
"index 44b0e0c..2393b4c 100644",
|
||||
"--- a/singleton-method-declaration.rb",
|
||||
"+++ b/singleton-method-declaration.rb",
|
||||
"@@ -1,4 +1,5 @@",
|
||||
"-def self.foo",
|
||||
"+def self.bar(a)",
|
||||
"+ baz",
|
||||
" end",
|
||||
" def self.foo",
|
||||
" end"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "9be301df5bd043c27ece14f9ea370518be524a3b..ec0380330945735057c42d735389cd3e3e19645c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-singleton-method-declaration-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"singleton-method-declaration.rb": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
3,
|
||||
4
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'self.bar(a)' method"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
4,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
4
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'self.foo()' method"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
3,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
5,
|
||||
4
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'self.bar(a)' method"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"singleton-method-declaration.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/singleton-method-declaration.rb b/singleton-method-declaration.rb",
|
||||
"index 2393b4c..84f3a03 100644",
|
||||
"--- a/singleton-method-declaration.rb",
|
||||
"+++ b/singleton-method-declaration.rb",
|
||||
"@@ -1,7 +1,5 @@",
|
||||
"-def self.bar(a)",
|
||||
"- baz",
|
||||
"-end",
|
||||
" def self.foo",
|
||||
" end",
|
||||
"-def self.foo",
|
||||
"+def self.bar(a)",
|
||||
"+ baz",
|
||||
" end"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "ec0380330945735057c42d735389cd3e3e19645c..9caba032307eb93717d1c08d5e01ddb3571efcf0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-singleton-method-declaration-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"singleton-method-declaration.rb": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
4
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'self.foo()' method"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"singleton-method-declaration.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/singleton-method-declaration.rb b/singleton-method-declaration.rb",
|
||||
"index 84f3a03..8649965 100644",
|
||||
"--- a/singleton-method-declaration.rb",
|
||||
"+++ b/singleton-method-declaration.rb",
|
||||
"@@ -1,5 +1,3 @@",
|
||||
"-def self.foo",
|
||||
"-end",
|
||||
" def self.bar(a)",
|
||||
" baz",
|
||||
" end"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "9caba032307eb93717d1c08d5e01ddb3571efcf0..0e43ebdc7453b47a1114fb4c95038938ab9fb544"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-singleton-method-declaration-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"singleton-method-declaration.rb": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
3,
|
||||
4
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'self.bar(a)' method"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"singleton-method-declaration.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/singleton-method-declaration.rb b/singleton-method-declaration.rb",
|
||||
"index 8649965..e69de29 100644",
|
||||
"--- a/singleton-method-declaration.rb",
|
||||
"+++ b/singleton-method-declaration.rb",
|
||||
"@@ -1,3 +0,0 @@",
|
||||
"-def self.bar(a)",
|
||||
"- baz",
|
||||
"-end"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "0e43ebdc7453b47a1114fb4c95038938ab9fb544..bdea1962c3afcde91a03aede5401db0e943ab608"
|
||||
}]
|
@ -1 +1 @@
|
||||
Subproject commit 177fb35939c02b4bc6067142eab57a6cc2237513
|
||||
Subproject commit 852d29d2b9a695875dd0e15454330bbf7c5e49ff
|
@ -1 +1 @@
|
||||
Subproject commit 65e9e9e96571a8ccd1c8e2e3fef5dc47a03b9a1e
|
||||
Subproject commit bdea1962c3afcde91a03aede5401db0e943ab608
|
Loading…
Reference in New Issue
Block a user