1
1
mirror of https://github.com/github/semantic.git synced 2024-12-23 23:11:50 +03:00

Merge branch 'master' into parser-option

This commit is contained in:
Rick Winfrey 2016-11-22 15:19:30 -06:00
commit bab0debf6d
266 changed files with 70167 additions and 5657 deletions

5
.gitmodules vendored
View File

@ -22,9 +22,12 @@
[submodule "vendor/hspec-expectations-pretty-diff"]
path = vendor/hspec-expectations-pretty-diff
url = https://github.com/rewinfrey/hspec-expectations-pretty-diff
[submodule "test/corpus/repos/go"]
path = test/corpus/repos/go
url = https://github.com/diff-fixtures/go.git
[submodule "test/corpus/repos/ruby"]
path = test/corpus/repos/ruby
url = https://github.com/diff-fixtures/ruby.git
[submodule "vendor/effects"]
path = vendor/effects
url = git@github.com:joshvera/effects.git
url = https://github.com/joshvera/effects.git

View File

@ -125,9 +125,10 @@ runCommitsAndTestCasesGeneration opts metaRepo@JSONMetaRepo{..} =
generate :: JSONMetaSyntax -> IO ()
generate metaSyntax = do
_ <- runInitialCommitForSyntax metaRepo metaSyntax
runSetupTestCaseFile $ testCaseFilePath language opts metaSyntax
runCommitAndTestCaseGeneration opts metaRepo metaSyntax (testCaseFilePath language opts metaSyntax)
runCloseTestCaseFile $ testCaseFilePath language opts metaSyntax
let testCaseFilePath' = testCaseFilePath language opts metaSyntax
runSetupTestCaseFile testCaseFilePath'
runCommitAndTestCaseGeneration opts metaRepo metaSyntax testCaseFilePath'
runCloseTestCaseFile testCaseFilePath'
testCaseFilePath :: String -> GeneratorArgs -> JSONMetaSyntax -> FilePath
testCaseFilePath language GeneratorArgs{..} JSONMetaSyntax{..} = case generateFormat of
@ -137,12 +138,23 @@ runCommitsAndTestCasesGeneration opts metaRepo@JSONMetaRepo{..} =
-- | For a syntax, we want the initial commit to be an empty file.
-- | This function performs a touch and commits the empty file.
runInitialCommitForSyntax :: JSONMetaRepo -> JSONMetaSyntax -> IO ()
runInitialCommitForSyntax JSONMetaRepo{..} JSONMetaSyntax{..} = do
runInitialCommitForSyntax metaRepo@JSONMetaRepo{..} metaSyntax@JSONMetaSyntax{..} = do
Prelude.putStrLn $ "Generating initial commit for " <> syntax <> " syntax."
result <- try . executeCommand (repoPath language) $ touchCommand (syntax <> fileExt) <> commitCommand syntax "Initial commit"
let repoFilePath' = repoFilePath metaRepo metaSyntax
result <- try . executeCommand (repoPath language) $ touchCommand repoFilePath' <> commitCommand syntax "Initial commit"
case ( result :: Either Prelude.IOError String) of
Left error -> Prelude.putStrLn $ "Initializing the " <> syntax <> fileExt <> " failed with: " <> show error <> ". " <> "Possible reason: file already initialized. \nProceeding to the next step."
Right _ -> pure ()
Left error -> Prelude.putStrLn $ "Initializing the " <> repoFilePath metaRepo metaSyntax <> " failed with: " <> show error <> ". " <> "Possible reason: file already initialized. \nProceeding to the next step."
Right _ -> runAddTemplateForSyntax metaRepo metaSyntax
runAddTemplateForSyntax :: JSONMetaRepo -> JSONMetaSyntax -> IO ()
runAddTemplateForSyntax metaRepo@JSONMetaRepo{..} metaSyntax@JSONMetaSyntax{..} = case templateText of
Just templateText -> do
let repoFilePath' = repoFilePath metaRepo metaSyntax
_ <- executeCommand (repoPath language) $ fileWriteCommand repoFilePath' templateText <> commitCommand syntax ("Add " <> repoFilePath' <> " template text.")
pure ()
Nothing -> pure ()
-- | Initializes the test case file where JSONTestCase examples are written to.
-- | This manually inserts a "[" to open a JSON array.
@ -180,14 +192,16 @@ runGenerateCommitAndTestCase opts JSONMetaRepo{..} testCaseFilePath (JSONMetaSyn
_ <- executeCommand (repoPath language) command
afterSha <- executeCommand (repoPath language) getLastCommitShaCommand
patch <- executeCommand (repoPath language) (gitDiffCommand beforeSha afterSha)
expectedResult' <- runExpectedResult (repoPath language) beforeSha afterSha (syntax <> fileExt) opts
let jsonTestCase = encodePretty JSONTestCase {
gitDir = extractGitDir (repoPath language),
testCaseDescription = language <> "-" <> syntax <> "-" <> description <> "-" <> "test",
filePaths = [syntax <> fileExt],
sha1 = beforeSha,
sha2 = afterSha,
shas = beforeSha <> ".." <> afterSha,
patch = lines patch,
expectedResult = expectedResult'
}
@ -243,21 +257,36 @@ generateJSON args = do
let rows = fromMaybe (fromList [("rows", "")]) headResult ! "rows"
pure $ JSONResult ( Map.fromList [ ("oids", oids), ("paths", paths), ("rows", rows) ] )
repoFilePath :: JSONMetaRepo -> JSONMetaSyntax -> String
repoFilePath metaRepo metaSyntax = syntax metaSyntax <> fileExt metaRepo
-- | Commands represent the various combination of patches (insert, delete, replacement)
-- | for a given syntax.
commands :: JSONMetaRepo -> JSONMetaSyntax -> [(JSONMetaSyntax, String, String, String)]
commands JSONMetaRepo{..} metaSyntax@JSONMetaSyntax{..} =
[ (metaSyntax, "insert", commaSeperator, fileWriteCommand repoFilePath insert <> commitCommand syntax "insert")
, (metaSyntax, "replacement-insert", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [replacement, insert, insert]) <> commitCommand syntax "replacement + insert + insert")
, (metaSyntax, "delete-insert", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [insert, insert, insert]) <> commitCommand syntax "delete + insert")
, (metaSyntax, "replacement", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [replacement, insert, insert]) <> commitCommand syntax "replacement")
, (metaSyntax, "delete-replacement", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [insert, replacement]) <> commitCommand syntax "delete + replacement")
, (metaSyntax, "delete", commaSeperator, fileWriteCommand repoFilePath replacement <> commitCommand syntax "delete")
, (metaSyntax, "delete-rest", spaceSeperator, removeCommand repoFilePath <> touchCommand repoFilePath <> commitCommand syntax "delete rest")
]
commands JSONMetaRepo{..} metaSyntax@JSONMetaSyntax{..} = case template of
(Just _) -> [ (metaSyntax, "setup", commaSeperator, fileWriteCommand repoFilePath (withTemplate "") <> commitCommand syntax "setup")
, (metaSyntax, "insert", commaSeperator, fileWriteCommand repoFilePath (withTemplate insert) <> commitCommand syntax "insert")
, (metaSyntax, "replacement", commaSeperator, fileWriteCommand repoFilePath (withTemplate replacement) <> commitCommand syntax "replacement")
, (metaSyntax, "delete-replacement", commaSeperator, fileWriteCommand repoFilePath (withTemplate insert) <> commitCommand syntax "delete replacement")
, (metaSyntax, "delete-insert", commaSeperator, fileWriteCommand repoFilePath (withTemplate "") <> commitCommand syntax "delete insert")
, (metaSyntax, "teardown", spaceSeperator, removeCommand repoFilePath <> touchCommand repoFilePath <> commitCommand syntax "teardown")
]
Nothing -> [ (metaSyntax, "insert", commaSeperator, fileWriteCommand repoFilePath insert <> commitCommand syntax "insert")
, (metaSyntax, "replacement-insert", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [replacement, insert, insert]) <> commitCommand syntax "replacement + insert + insert")
, (metaSyntax, "delete-insert", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [insert, insert, insert]) <> commitCommand syntax "delete + insert")
, (metaSyntax, "replacement", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [replacement, insert, insert]) <> commitCommand syntax "replacement")
, (metaSyntax, "delete-replacement", commaSeperator, fileWriteCommand repoFilePath (Prologue.intercalate "\n" [insert, replacement]) <> commitCommand syntax "delete + replacement")
, (metaSyntax, "delete", commaSeperator, fileWriteCommand repoFilePath replacement <> commitCommand syntax "delete")
, (metaSyntax, "delete-rest", spaceSeperator, removeCommand repoFilePath <> touchCommand repoFilePath <> commitCommand syntax "delete rest")
]
where commaSeperator = "\n,"
spaceSeperator = ""
repoFilePath = syntax <> fileExt
withTemplate = contentsWithTemplate template
contentsWithTemplate :: Maybe String -> String -> String
contentsWithTemplate (Just template) contents = DT.unpack $ DT.replace "{0}" (toS contents) (toS template)
contentsWithTemplate Nothing contents = contents
-- | Attempts to pull from the git repository's remote repository.
-- | If the pull fails, the exception is caught and continues to the next step.
@ -304,6 +333,9 @@ addSubmoduleCommand repoUrl repoPath = "git submodule add " <> repoUrl <> " " <>
getLastCommitShaCommand :: String
getLastCommitShaCommand = "git log --pretty=format:\"%H\" -n 1;"
gitDiffCommand :: String -> String -> String
gitDiffCommand sha1 sha2 = "git diff " <> sha1 <> ".." <> sha2 <> ";"
checkoutMasterCommand :: String
checkoutMasterCommand = "git checkout master;"
@ -322,6 +354,12 @@ fileWriteCommand repoFilePath contents = "echo \"" <> (escapeBackticks . escapeD
escapeBackticks = DSUtils.replace "`" "\\`"
escapeDoubleQuotes = DSUtils.replace "\"" "\\\""
fileAppendCommand :: FilePath -> String -> String
fileAppendCommand repoFilePath contents = "echo \"" <> (escapeBackticks . escapeDoubleQuotes) contents <> "\" >> " <> repoFilePath <> ";"
where
escapeBackticks = DSUtils.replace "`" "\\`"
escapeDoubleQuotes = DSUtils.replace "\"" "\\\""
commitCommand :: String -> String -> String
commitCommand syntax commitMessage = "git add .; git commit -m \"" <> syntax <> ": " <> commitMessage <> "\"" <> ";"

View File

@ -34,6 +34,7 @@ library
, Language.C
, Language.JavaScript
, Language.Markdown
, Language.Go
, Language.Ruby
, Parse
, Parser
@ -56,6 +57,9 @@ library
, Term
, Term.Arbitrary
, TreeSitter
, FDoc.Term
, FDoc.RecursionSchemes
, FDoc.NatExample
build-depends: base >= 4.8 && < 5
, aeson
, aeson-pretty
@ -197,6 +201,7 @@ test-suite integration-test
, hspec >= 2.1.10
, hspec-expectations-pretty-diff
, semantic-diff
, split
, MissingH
, unordered-containers
ghc-options: -threaded -rtsopts -with-rtsopts=-N -j -pgml=script/g++

View File

@ -116,6 +116,8 @@ data Category
| Import
-- | An export
| Export
-- | An anonymous function.
| AnonymousFunction
-- | An interpolation (e.g. "#{bar}" in Ruby)
| Interpolation
-- | A subshell command (e.g. `ls -la` in Ruby)
@ -128,6 +130,35 @@ data Category
| Until
-- | A unless/else expression.
| Unless
| Begin
| Else
| Elsif
| Ensure
| Rescue
| RescueModifier
| RescuedException
| RescueArgs
| When
| Negate
-- | A select expression in Go.
| Select
| Defer
| Go
| Slice
| TypeAssertion
| TypeConversion
-- | An argument pair, e.g. foo(run: true) or foo(:run => true) in Ruby.
| ArgumentPair
-- | A keyword parameter, e.g. def foo(name:) or def foo(name:false) in Ruby.
| KeywordParameter
-- | An optional/default parameter, e.g. def foo(name = nil) in Ruby.
| OptionalParameter
-- | A splat parameter, e.g. def foo(*array) in Ruby.
| SplatParameter
-- | A hash splat parameter, e.g. def foo(**option) in Ruby.
| HashSplatParameter
-- | A block parameter, e.g. def foo(&block) in Ruby.
| BlockParameter
deriving (Eq, Generic, Ord, Show)
-- Instances
@ -191,6 +222,28 @@ instance Arbitrary Category where
, pure Yield
, pure Until
, pure Unless
, pure Begin
, pure Else
, pure Elsif
, pure Ensure
, pure Rescue
, pure RescueModifier
, pure RescuedException
, pure RescueArgs
, pure When
, pure Negate
, pure Select
, pure Defer
, pure Go
, pure Slice
, pure TypeAssertion
, pure TypeConversion
, pure ArgumentPair
, pure KeywordParameter
, pure OptionalParameter
, pure SplatParameter
, pure HashSplatParameter
, pure BlockParameter
, Other <$> arbitrary
]

View File

@ -37,6 +37,7 @@ import Data.These
import Diff
type Label f fields label = forall b. TermF f (Record fields) b -> label
type DiffTerms f fields = Term f (Record fields) -> Term f (Record fields) -> Maybe (Diff f (Record fields))
-- | Given a function comparing two terms recursively,
-- a function to compute a Hashable label from an unpacked term, and two lists of terms,
@ -45,12 +46,8 @@ type Label f fields label = forall b. TermF f (Record fields) b -> label
--
-- This implementation is based on the paper [_RWS-Diff—Flexible and Efficient Change Detection in Hierarchical Data_](https://github.com/github/semantic-diff/files/325837/RWS-Diff.Flexible.and.Efficient.Change.Detection.in.Hierarchical.Data.pdf).
rws :: forall f fields label.
(GAlign f,
Traversable f,
Eq (f (Term f Category)),
Hashable label,
HasField fields Category)
=> (Term f (Record fields) -> Term f (Record fields) -> Maybe (Diff f (Record fields))) -- ^ A function which compares a pair of terms recursively, returning 'Just' their diffed value if appropriate, or 'Nothing' if they should not be compared.
(GAlign f, Traversable f, Eq (f (Term f Category)), Hashable label, HasField fields Category)
=> DiffTerms f fields -- ^ A function which compares a pair of terms recursively, returning 'Just' their diffed value if appropriate, or 'Nothing' if they should not be compared.
-> Label f fields label
-> [Term f (Record fields)] -- ^ The list of old terms.
-> [Term f (Record fields)] -- ^ The list of new terms.
@ -220,7 +217,11 @@ defaultM :: Integer
defaultM = 10
-- | A term which has not yet been mapped by `rws`, along with its feature vector summary & index.
data UnmappedTerm f fields = UnmappedTerm { termIndex :: Int, feature :: Vector.Vector Double, term :: (Term f (Record fields)) }
data UnmappedTerm f fields = UnmappedTerm {
termIndex :: Int -- ^ The index of the term within its root term.
, feature :: Vector.Vector Double -- ^ Feature vector
, term :: Term f (Record fields) -- ^ The unmapped term
}
-- | Either a `term`, an index of a matched term, or nil.
data TermOrIndexOrNil term = Term term | Index Int | Nil

View File

@ -17,7 +17,6 @@ type Diff f annotation = Free (TermF f (Both annotation)) (Patch (Term f annotat
type SyntaxDiff leaf fields = Diff (Syntax leaf) (Record fields)
type instance Base (Free f a) = FreeF f a
instance Functor f => Recursive (Free f a) where project = runFree
instance Functor f => Corecursive (Free f a) where embed = free

View File

@ -13,7 +13,8 @@ import Syntax as S
import Category as C
import Data.Functor.Both hiding (fst, snd)
import qualified Data.Functor.Both as Both
import Data.Text as Text (intercalate)
import Data.Text (intercalate)
import qualified Data.Text as Text (head)
import Test.QuickCheck hiding (Fixed)
import Patch.Arbitrary()
import Data.Record
@ -47,12 +48,20 @@ identifiable term = isIdentifiable (unwrap term) term
S.MathAssignment{} -> Identifiable
S.VarAssignment{} -> Identifiable
S.SubscriptAccess{} -> Identifiable
S.Module{} -> Identifiable
S.Class{} -> Identifiable
S.Method{} -> Identifiable
S.Leaf{} -> Identifiable
S.DoWhile{} -> Identifiable
S.Import{} -> Identifiable
S.Export{} -> Identifiable
S.Ternary{} -> Identifiable
S.If{} -> Identifiable
S.Try{} -> Identifiable
S.Switch{} -> Identifiable
S.Case{} -> Identifiable
S.Rescue{} -> Identifiable
S.Pair{} -> Identifiable
_ -> Unidentifiable
data JSONSummary summary span = JSONSummary { summary :: summary, span :: span }
@ -139,6 +148,11 @@ determiner :: DiffInfo -> Doc
determiner (LeafInfo "number" _ _) = ""
determiner (LeafInfo "integer" _ _) = ""
determiner (LeafInfo "boolean" _ _) = ""
determiner (LeafInfo "begin statement" _ _) = "a"
determiner (LeafInfo "select statement" _ _) = "a"
determiner (LeafInfo "else block" _ _) = "an"
determiner (LeafInfo "ensure block" _ _) = "an"
determiner (LeafInfo "when block" _ _) = "a"
determiner (LeafInfo "anonymous function" _ _) = "an"
determiner (BranchInfo bs _ _) = determiner (last bs)
determiner _ = "the"
@ -152,6 +166,11 @@ toLeafInfos leaf = pure . flip JSONSummary (sourceSpan leaf) $ case leaf of
(LeafInfo "integer" termName _) -> squotes $ toDoc termName
(LeafInfo "boolean" termName _) -> squotes $ toDoc termName
(LeafInfo "anonymous function" termName _) -> toDoc termName <+> "function"
(LeafInfo cName@"begin statement" _ _) -> toDoc cName
(LeafInfo cName@"select statement" _ _) -> toDoc cName
(LeafInfo cName@"else block" _ _) -> toDoc cName
(LeafInfo cName@"ensure block" _ _) -> toDoc cName
(LeafInfo cName@"when block" _ _) -> toDoc cName
(LeafInfo cName@"string" termName _) -> toDoc termName <+> toDoc cName
(LeafInfo cName@"export statement" termName _) -> toDoc termName <+> toDoc cName
(LeafInfo cName@"import statement" termName _) -> toDoc termName <+> toDoc cName
@ -162,8 +181,12 @@ toLeafInfos leaf = pure . flip JSONSummary (sourceSpan leaf) $ case leaf of
-- Returns a text representing a specific term given a source and a term.
toTermName :: forall leaf fields. (HasCategory leaf, DefaultFields fields) => Source Char -> SyntaxTerm leaf fields -> Text
toTermName source term = case unwrap term of
S.TypeAssertion _ _ -> termNameFromSource term
S.TypeConversion _ _ -> termNameFromSource term
S.Go expr -> toTermName' expr
S.Defer expr -> toTermName' expr
S.AnonymousFunction params _ -> "anonymous" <> paramsToArgNames params
S.Fixed children -> fromMaybe "branch" $ (toCategoryName . category) . extract <$> head children
S.Fixed children -> termNameFromChildren term children
S.Indexed children -> fromMaybe "branch" $ (toCategoryName . category) . extract <$> head children
Leaf leaf -> toCategoryName leaf
S.Assignment identifier _ -> toTermName' identifier
@ -192,18 +215,15 @@ toTermName source term = case unwrap term of
(_, _) -> toTermName' base <> "[" <> toTermName' element <> "]"
S.VarAssignment varId _ -> toTermName' varId
S.VarDecl decl -> toTermName' decl
-- TODO: We should remove Args from Syntax since I don't think we should ever
-- evaluate Args as a single toTermName Text - joshvera
S.Args args -> mconcat $ toTermName' <$> args
-- TODO: We should remove Case from Syntax since I don't think we should ever
-- evaluate Case as a single toTermName Text - joshvera
S.Case expr _ -> toTermName' expr
S.Case expr _ -> termNameFromSource expr
S.Switch expr _ -> toTermName' expr
S.Ternary expr _ -> toTermName' expr
S.MathAssignment id _ -> toTermName' id
S.Operator _ -> termNameFromSource term
S.Object kvs -> "{ " <> intercalate ", " (toTermName' <$> kvs) <> " }"
S.Pair a _ -> toTermName' a <> ": …"
S.Pair k v -> toKeyName k <> toArgName v
S.Return expr -> maybe "empty" toTermName' expr
S.Yield expr -> maybe "empty" toTermName' expr
S.Error _ -> termNameFromSource term
@ -213,10 +233,11 @@ toTermName source term = case unwrap term of
S.DoWhile _ expr -> toTermName' expr
S.Throw expr -> termNameFromSource expr
S.Constructor expr -> toTermName' expr
S.Try expr _ _ -> termNameFromSource expr
S.Try clauses _ _ _ -> termNameFromChildren term clauses
S.Select clauses -> termNameFromChildren term clauses
S.Array _ -> termNameFromSource term
S.Class identifier _ _ -> toTermName' identifier
S.Method identifier _ _ -> toTermName' identifier
S.Method identifier args _ -> toTermName' identifier <> paramsToArgNames args
S.Comment a -> toCategoryName a
S.Commented _ _ -> termNameFromChildren term (toList $ unwrap term)
S.Module identifier _ -> toTermName' identifier
@ -226,8 +247,8 @@ toTermName source term = case unwrap term of
S.Export (Just identifier) [] -> "{ " <> toTermName' identifier <> " }"
S.Export (Just identifier) expr -> "{ " <> intercalate ", " (termNameFromSource <$> expr) <> " }" <> " from " <> toTermName' identifier
S.ConditionalAssignment id _ -> toTermName' id
S.Until expr _ -> toTermName' expr
S.Unless expr _ -> termNameFromSource expr
S.Negate expr -> toTermName' expr
S.Rescue args _ -> intercalate ", " $ toTermName' <$> args
where toTermName' = toTermName source
termNameFromChildren term children = termNameFromRange (unionRangesFrom (range term) (range <$> children))
termNameFromSource term = termNameFromRange (range term)
@ -238,12 +259,30 @@ toTermName source term = case unwrap term of
toArgName arg = case identifiable arg of
Identifiable arg -> toTermName' arg
Unidentifiable _ -> ""
toKeyName key = case toTermName' key of
n | Text.head n == ':' -> n <> " => "
n -> n <> ": "
parentContexts :: [Either (Category, Text) (Category, Text)] -> Doc
parentContexts contexts = hsep $ either identifiableDoc annotatableDoc <$> contexts
where
identifiableDoc (c, t) = case c of
C.Assignment -> "in an" <+> catName c <+> "to" <+> termName t
C.Select -> "in a" <+> catName c
C.Begin -> "in a" <+> catName c
C.Else -> "in an" <+> catName c
C.Elsif -> "in the" <+> squotes (termName t) <+> catName c
C.Method -> "in the" <+> squotes (termName t) <+> catName c
C.Ternary -> "in the" <+> squotes (termName t) <+> catName c
C.Ensure -> "in an" <+> catName c
C.Rescue -> case t of
"" -> "in a" <+> catName c
_ -> "in the" <+> squotes (termName t) <+> catName c
C.RescueModifier -> "in the" <+> squotes ("rescue" <+> termName t) <+> "modifier"
C.If -> "in the" <+> squotes (termName t) <+> catName c
C.Case -> "in the" <+> squotes (termName t) <+> catName c
C.Switch -> "in the" <+> squotes (termName t) <+> catName c
C.When -> "in a" <+> catName c
_ -> "in the" <+> termName t <+> catName c
annotatableDoc (c, t) = "of the" <+> squotes (termName t) <+> catName c
catName = toDoc . toCategoryName
@ -324,7 +363,7 @@ instance HasCategory Category where
NumberLiteral -> "number"
Other s -> s
C.Pair -> "pair"
Params -> "params"
C.Params -> "params"
Program -> "top level"
Regex -> "regex"
StringLiteral -> "string"
@ -348,12 +387,35 @@ instance HasCategory Category where
C.Module -> "module"
C.Import -> "import statement"
C.Export -> "export statement"
C.AnonymousFunction -> "anonymous function"
C.Interpolation -> "interpolation"
C.Subshell -> "subshell command"
C.ConditionalAssignment -> "conditional assignment"
C.Yield -> "yield statement"
C.Until -> "until statement"
C.Unless -> "unless statement"
C.Begin -> "begin statement"
C.Else -> "else block"
C.Elsif -> "elsif block"
C.Ensure -> "ensure block"
C.Rescue -> "rescue block"
C.RescueModifier -> "rescue modifier"
C.When -> "when comparison"
C.RescuedException -> "last exception"
C.RescueArgs -> "arguments"
C.Negate -> "negate"
C.Select -> "select statement"
C.Go -> "go statement"
C.Slice -> "slice expression"
C.Defer -> "defer statement"
C.TypeAssertion -> "type assertion statement"
C.TypeConversion -> "type conversion expression"
C.ArgumentPair -> "argument"
C.KeywordParameter -> "parameter"
C.OptionalParameter -> "parameter"
C.SplatParameter -> "parameter"
C.HashSplatParameter -> "parameter"
C.BlockParameter -> "parameter"
instance HasField fields Category => HasCategory (SyntaxTerm leaf fields) where
toCategoryName = toCategoryName . category . extract

View File

@ -36,23 +36,23 @@ diffFiles :: (HasField fields Category, HasField fields Cost)
-> Renderer (Record fields)
-> Both SourceBlob
-> IO Output
diffFiles parser renderer sourceBlobs = do
terms <- traverse parser sourceBlobs
diffFiles parse render sourceBlobs = do
terms <- traverse parse sourceBlobs
pure $! render sourceBlobs (diffTerms' terms)
let areNullOids = runBothWith (\a b -> (oid a == nullOid || null (source a), oid b == nullOid || null (source b))) sourceBlobs
let textDiff = case areNullOids of
where
diffTerms' terms = case runBothWith areNullOids sourceBlobs of
(True, False) -> pure $ Insert (snd terms)
(False, True) -> pure $ Delete (fst terms)
(_, _) ->
runBothWith (diffTerms construct compareCategoryEq diffCostWithCachedTermCosts getLabel) terms
pure $! renderer sourceBlobs textDiff
where construct (info :< syntax) = free (Free ((setCost <$> info <*> sumCost syntax) :< syntax))
sumCost = fmap getSum . foldMap (fmap Sum . getCost)
getCost diff = case runFree diff of
Free (info :< _) -> cost <$> info
Pure patch -> uncurry both (fromThese 0 0 (unPatch (cost . extract <$> patch)))
areNullOids a b = (hasNullOid a, hasNullOid b)
hasNullOid blob = oid blob == nullOid || null (source blob)
construct (info :< syntax) = free (Free ((setCost <$> info <*> sumCost syntax) :< syntax))
sumCost = fmap getSum . foldMap (fmap Sum . getCost)
getCost diff = case runFree diff of
Free (info :< _) -> cost <$> info
Pure patch -> uncurry both (fromThese 0 0 (unPatch (cost . extract <$> patch)))
getLabel :: HasField fields Category => CofreeF (Syntax leaf) (Record fields) b -> (Category, Maybe leaf)
getLabel (h :< t) = (category h, case t of
@ -89,13 +89,15 @@ truncatedDiff arguments sources = pure $ case format arguments of
printDiff :: (ToJSON (Record fields), DefaultFields fields, HasField fields Cost) => Parser (Syntax Text) (Record fields) -> DiffArguments -> Both SourceBlob -> IO ()
printDiff parser arguments sources = do
rendered <- textDiff parser arguments sources
let renderedText = case rendered of
SplitOutput text -> text
PatchOutput text -> text
JSONOutput series -> toS . encodingToLazyByteString . toEncoding $ toJSON series
SummaryOutput summaries -> toS . encodingToLazyByteString . toEncoding $ toJSON summaries
writeToOutput (output arguments) renderedText
writeToOutput (output arguments) $
case rendered of
SplitOutput text -> text
PatchOutput text -> text
JSONOutput series -> encodingToText (toJSON series)
SummaryOutput summaries -> encodingToText (toJSON summaries)
where
-- TODO: Don't go from Value to Text?
encodingToText = toS . encodingToLazyByteString . toEncoding
-- | Writes text to an output file or stdout.
writeToOutput :: Maybe FilePath -> Text -> IO ()

57
src/FDoc/NatExample.hs Normal file
View File

@ -0,0 +1,57 @@
module FDoc.NatExample where
import Prologue
import Data.Functor.Foldable
-- Our base Functor. The recursive bit is parameterized by r.
data NatF r =
ZeroF
| SuccF r
deriving (Show, Functor)
-- Fix represents the "fixed point" for the NatF Functor, and enables recursion.
-- Important to note this has kind * -> *.
type Nat = Fix NatF
-- This is a fully applied type (Has kind *).
zero' :: Nat
zero' = Fix ZeroF
-- This is a partially applied type (has kind * -> *). The recursive bit is used by recursion schemes and is referred to as the "carrier" functor.
succ' :: Nat -> Nat
succ' = Fix . SuccF
-- Catamorphism: "tear down" a recursive structure in the shape of Nat.
natToIntCata :: Nat -> Int
natToIntCata nats = cata algebra nats
where
algebra term = case term of
ZeroF -> 0
SuccF value -> 1 + value
-- Anamorphism: "build up" a recursive structure in the shape of Nat.
intToNatAna :: Int -> Nat
intToNatAna num = ana coalgebra num
where
coalgebra num = case num of
0 -> ZeroF
_ -> SuccF (num - 1)
-- Hylomorphism: first apply an anamorphism and then a catamorphism in the shape of Nat.
natHylo :: Int -> Int
natHylo num = hylo algebra coalgebra num
where
algebra term = case term of
ZeroF -> 0
SuccF value -> 1 + value
coalgebra num = case num of
0 -> ZeroF
_ -> SuccF (num - 1)
-- Paramorphism: primitive recursion maintaining the original value along with its computed value.
natPara :: Nat -> Int
natPara nats = para algebra nats
where
algebra value = case value of
ZeroF -> 0
(SuccF (_, value')) -> 1 + value'

View File

@ -0,0 +1,163 @@
{-# LANGUAGE DataKinds, ScopedTypeVariables, TypeFamilies, TypeOperators #-}
module FDoc.RecursionSchemes where
import Data.Record
import Range
import Category
import Term
import Syntax
import Prologue
import Prelude
import Data.Functor.Foldable hiding (ListF)
import FDoc.Term
data NewField = NewField deriving (Show)
{-
Anamorphism -- add a new field to each term's Record fields
ana :: (a -> Base t a) -- a (Base t)-coalgebra
-> a -- seed
-> t -- resulting fixed point
Anamorphism as a recursion scheme "builds up" a recursive structure. Anamorphisms work by using a coalgebra, which maps a seed value to a fixed point structure.
The example below adds a new field to the `Record` fields.
-}
indexedTermAna :: [leaf] -> Term (Syntax leaf) (Record '[NewField, Range, Category])
indexedTermAna childrenLeaves = ana coalgebra (indexedTerm childrenLeaves)
where
coalgebra term = (NewField .: (extract term)) :< unwrap term
{-
Catamorphism example -- add a new field to each term's Record fields
cata :: (Base t a -> a) -- a (Base t)-algebra
-> t -- fixed point
-> a -- result
Catamorphism as a recursion scheme "tears down" a recursive structure. Catamorphisms work by using an algebra, which maps a shape in our fixed point structure to a new shape.
The example below adds a new field to the `Record` fields.
-}
indexedTermCata :: [leaf] -> Term (Syntax leaf) (Record '[NewField, Range, Category])
indexedTermCata childrenLeaves = cata algebra (indexedTerm childrenLeaves)
where
algebra term = cofree $ (NewField .: (headF term)) :< tailF term
{-
Anamorphism -- construct a Term from a string
The example below shows how to build up a recursive Term structure from a string representation.
Example usage:
stringToTermAna "indexed" =>
CofreeT (Identity ( (Range {start = 1, end = 10} .: MethodCall .: RNil)
:<
Indexed
[ CofreeT (Identity ( (Range {start = 1, end = 10} .: MethodCall .: RNil) :< Leaf "leaf1" ) )
, CofreeT (Identity ( (Range {start = 1, end = 10} .: MethodCall .: RNil) :< Leaf "leaf2" ) )
, CofreeT (Identity ( (Range {start = 1, end = 10} .: MethodCall .: RNil) :< Leaf "leaf3" ) )
] ))
First step is to match against the "indexed" string and begin building up a Cofree Indexed structure:
CofreeT (Identity ( (Range 1 10 .: Category.MethodCall .: RNil) :< Indexed ["leaf1", "leaf2", "leaf3"] ) )
While building up the `Indexed` structure, we continue to recurse over the `Indexed` terms ["leaf1", "leaf2", "leaf3"]. These are pattern matched using the catch all `_` and default to `Leaf` Syntax shapes:
CofreeT (Identity ( (Range 1 10 .: Category.MethodCall .: RNil) :< Leaf "leaf1" ) )
CofreeT (Identity ( (Range 1 10 .: Category.MethodCall .: RNil) :< Leaf "leaf2" ) )
CofreeT (Identity ( (Range 1 10 .: Category.MethodCall .: RNil) :< Leaf "leaf3" ) )
These structures are substituted in place of ["leaf1", "leaf2", "leaf3"] in the new cofree `Indexed` structure, resulting in a expansion of all possible string terms.
-}
stringToTermAna :: String -> Term (Syntax String) (Record '[Range, Category])
stringToTermAna = ana coalgebra
where
coalgebra representation = case representation of
"indexed" -> (Range 1 10 .: Category.MethodCall .: RNil) :< Indexed ["leaf1", "leaf2", "leaf3"]
_ -> (Range 1 10 .: Category.MethodCall .: RNil) :< Leaf representation
{-
Catamorphism -- construct a list of Strings from a recursive Term structure.
The example below shows how to tear down a recursive Term structure into a list of String representation.
-}
termToStringCata :: Term (Syntax String) (Record '[Range, Category]) -> [String]
termToStringCata = cata algebra
where
algebra term = case term of
(_ :< Leaf value) -> [value]
(_ :< Indexed values) -> ["indexed"] <> Prologue.concat values
_ -> ["unknown"]
{-
Hylomorphism -- An anamorphism followed by a catamorphism
hylo :: Functor f => (f b -> b) -- an algebra
-> (a -> f a) -- a coalgebra
-> a -- seed value
-> b -- result
Hylomorphisms work by first applying a coalgebra (anamorphism) to build up a structure. An algebra (catamorphism) is then applied to this structure. Because of fusion the anamorphism and catamorphism occur in a single pass rather than two separate traversals.
The example below shows how our algebra and coalgebra defined in the termToStringCata and stringToTermAna can be utilized as a hylomorphism.
Example Usage:
stringTermHylo "indexed" => ["indexed", "leaf1", "leaf2", "leaf3"]
-}
stringTermHylo :: String -> [String]
stringTermHylo = hylo algebra coalgebra
where
algebra term = case term of
(_ :< Leaf value) -> [value]
(_ :< Indexed values) -> ["indexed"] <> Prologue.concat values
_ -> ["unknown"]
coalgebra stringRepresentation = case stringRepresentation of
"indexed" -> (Range 1 10 .: Category.MethodCall .: RNil) :< Indexed ["leaf1", "leaf2", "leaf3"]
_ -> (Range 1 10 .: Category.MethodCall .: RNil) :< Leaf stringRepresentation
{-
Paramorphism -- primitive recursion that maintains a reference to the original value and its computed value.
para :: (Base t (t, a) -> a) -- an algebra that takes a tuple of the last input
-> t -- fixed point
-> a -- result
Paramorphisms, like all recursion schemes, work via a bottom up traversal (leaves to root), in which an algebra is applied to every node in the recursive structure. The difference between paramorphisms and catamorphisms is the algebra receives a tuple of the original subobject and its computed value (t, a) where `t` is the original suboject and `a` is the computed value.
The example implementation below calculates a string representation for each Syntax type, flattening the recursive structure into a one dimensional list to tuples. The tuple contains the original syntax subobject, and its computed string representation. This example aims to showcase how paramorphisms work by returning a final list of tuples that mimics the intermediate tuple shapes the algebra receives throughout the bottom up traversal.
Example Usage:
let terms = indexedTerm ["leaf1", "leaf2", "leaf3"]
termPara terms = Recurse over the structure to start at the leaves (bottom up traversal):
tuple3 = ( CofreeT (Identity ((Range {start = 1, end = 10} .: MethodCall .: RNil) :< Leaf "leaf3")), "leaf3" ) : []
Continue the traversal from leaves to root:
tuple2:3 = ( CofreeT (Identity ((Range {start = 1, end = 10} .: MethodCall .: RNil) :< Leaf "leaf2")), "leaf2") : tuple3
tuple1:2:3 = ( CofreeT (Identity ((Range {start = 1, end = 10} .: MethodCall .: RNil) :< Leaf "leaf1" )), "leaf1") : tuple2:3
Compute the root:
tupleIndexed:1:2:3 = ( CofreeT (Identity ((Range {start = 1, end = 10} .: MethodCall .: RNil) :< Indexed [])), "indexed" ) : tuple1:2:3
Final shape:
[ (CofreeT (Identity ((Range {start = 1, end = 10} .: MethodCall .: RNil) :< Indexed [])) , "indexed")
, (CofreeT (Identity ((Range {start = 1, end = 10} .: MethodCall .: RNil) :< Leaf "leaf1")), "leaf1")
, (CofreeT (Identity ((Range {start = 1, end = 10} .: MethodCall .: RNil) :< Leaf "leaf2")), "leaf2")
, (CofreeT (Identity ((Range {start = 1, end = 10} .: MethodCall .: RNil) :< Leaf "leaf3")), "leaf3")
]
-}
termPara :: Term (Syntax String) (Record '[Range, Category]) -> [(Term (Syntax String) (Record '[Range, Category]), String)]
termPara = para algebra
where
algebra term = case term of
(annotation :< Leaf representation) -> [(cofree (annotation :< Leaf representation), representation)]
(annotation :< Indexed values) -> [(cofree (annotation :< Indexed []), "indexed")] <> (values >>= Prelude.snd)
_ -> [(cofree ((Range 1 10 .: Category.MethodCall .: RNil) :< Leaf "unknown"), "unknown")]

61
src/FDoc/Term.hs Normal file
View File

@ -0,0 +1,61 @@
{-# LANGUAGE DataKinds, TypeOperators #-}
module FDoc.Term where
import Data.Record
import Range
import Category
import Term
import Syntax
import Prologue
{-
Constructs a Syntax.Leaf using the polymorphic type variable `leaf`.
This is in the TermF shape: CofreeF f a b where
f is the functor (Syntax.Leaf `leaf`)
a is the annotation (Record '[Range, Category])
b is the same type of functor defined by f
Two common convenience operations when working with CofreeF (for docs, see Control.Comonad.Trans.Cofree.Types.CofreeF) are `headF` and `tailF`. `headF` return the annotation portion of the CofreeF structure, and `tailF` returns the functor portion (Syntax).
Example (from GHCi):
> let leaf = leafTermF "example"
> headF leaf
> Range {start = 1, end = 10} .: MethodCall .: RNil
> tailF leaf
> Leaf "example"
-}
leafTermF :: leaf -> TermF (Syntax leaf) (Record '[Range, Category]) b
leafTermF leaf = (Range 1 10 .: Category.MethodCall .: RNil) :< Leaf leaf
{-
Constructs a Syntax.Leaf using the polymorphic type variable `leaf`.
This is in the Term shape: Cofree f a where
f is the functor (Syntax.Leaf `leaf`)
a is the annotation (Record '[Range, Category])
Two common convenience operations when working with Cofree (for docs, see Control.Comonad.Trans.Cofree.Types.Cofree) are `extract` and `unwrap`. `extract` returns the annotation portion of the Cofree structure, and `unwrap` returns the functor portion (Syntax).
Example (from GHCi):
> let leaf = leafTerm "example"
> extract leaf
> Range {start = 1, end = 10} .: MethodCall .: RNil
> unwrap leaf
> Leaf "example"
-}
leafTerm :: leaf -> Cofree (Syntax leaf) (Record '[Range, Category])
leafTerm = cofree . leafTermF
indexedTermF :: [leaf] -> TermF (Syntax leaf) (Record '[Range, Category]) (Term (Syntax leaf) (Record '[Range, Category]))
indexedTermF leaves = (Range 1 10 .: Category.MethodCall .: RNil) :< (Indexed (leafTerm <$> leaves))
indexedTerm :: [leaf] -> Term (Syntax leaf) (Record '[Range, Category])
indexedTerm leaves = cofree $ indexedTermF leaves

View File

@ -54,7 +54,10 @@ algorithmWithTerms :: (TermF (Syntax leaf) (Both a) diff -> diff)
-> Term (Syntax leaf) a
-> Algorithm (Term (Syntax leaf) a) diff diff
algorithmWithTerms construct t1 t2 = maybe (recursively t1 t2) (fmap annotate) $ case (unwrap t1, unwrap t2) of
(Indexed a, Indexed b) -> Just $ Indexed <$> bySimilarity a b
(Indexed a, Indexed b) ->
Just $ Indexed <$> bySimilarity a b
(S.Module idA a, S.Module idB b) ->
Just $ S.Module <$> recursively idA idB <*> bySimilarity a b
(S.FunctionCall identifierA argsA, S.FunctionCall identifierB argsB) -> Just $
S.FunctionCall <$> recursively identifierA identifierB
<*> bySimilarity argsA argsB

View File

@ -27,6 +27,7 @@ data Language =
| R
| Ruby
| Swift
| Go
deriving (Show)
-- | Returns a Language based on the file extension (including the ".").
@ -37,6 +38,7 @@ languageForType mediaType = case mediaType of
".js" -> Just JavaScript
".md" -> Just Markdown
".rb" -> Just Ruby
".go" -> Just Language.Go
_ -> Nothing
termConstructor

189
src/Language/Go.hs Normal file
View File

@ -0,0 +1,189 @@
{-# LANGUAGE DataKinds #-}
module Language.Go where
import Prologue
import Info
import Source
import Term
import qualified Syntax as S
import Data.Record
import Range (unionRangesFrom)
import SourceSpan (unionSourceSpansFrom)
termConstructor
:: Source Char -- ^ The source that the term occurs within.
-> IO SourceSpan -- ^ The span that the term occupies. This is passed in 'IO' to guarantee some access constraints & encourage its use only when needed (improving performance).
-> Text -- ^ The name of the production for this node.
-> Range -- ^ The character range that the term occupies.
-> [ SyntaxTerm Text '[Range, Category, SourceSpan] ] -- ^ The child nodes of the term.
-> IO (SyntaxTerm Text '[Range, Category, SourceSpan]) -- ^ The resulting term, in IO.
termConstructor source sourceSpan name range children = case name of
"return_statement" -> withDefaultInfo $ S.Return (listToMaybe children)
"source_file" -> case children of
packageName : rest | category (extract packageName) == Other "package_clause" ->
case unwrap packageName of
S.Indexed [id] -> withCategory Module (S.Module id rest)
_ -> withCategory Error (S.Error children)
_ -> withCategory Error (S.Error children)
"import_declaration" -> toImports children
"function_declaration" -> withDefaultInfo $ case children of
[id, params, block] -> S.Function id (toList $ unwrap params) (toList $ unwrap block)
rest -> S.Error rest
"for_statement" ->
withDefaultInfo $ case children of
[body] | category (extract body) == Other "block" ->
S.For [] (toList $ unwrap body)
[forClause, body] | category (extract forClause) == Other "for_clause" ->
S.For (toList $ unwrap forClause) (toList $ unwrap body)
[rangeClause, body] | category (extract rangeClause) == Other "range_clause" ->
S.For (toList $ unwrap rangeClause) (toList $ unwrap body)
other -> S.Error other
"expression_switch_statement" ->
case Prologue.break isCaseClause children of
(clauses, cases) -> do
clauses' <- withDefaultInfo $ S.Indexed clauses
withDefaultInfo $ S.Switch clauses' cases
where isCaseClause = (== Case) . category . extract
"type_switch_statement" ->
case Prologue.break isCaseClause children of
(clauses, cases) -> do
withDefaultInfo $ case clauses of
[id] -> S.Switch id cases
_ -> S.Error children
where isCaseClause = (== Case) . category . extract
"select_statement" -> withDefaultInfo $ S.Select (toCommunicationCase =<< children)
where toCommunicationCase = toList . unwrap
"go_statement" -> withDefaultInfo $ toExpression S.Go children
"defer_statement" -> withDefaultInfo $ toExpression S.Defer children
"selector_expression" -> withDefaultInfo $ toSubscriptAccess children
"index_expression" -> withDefaultInfo $ toSubscriptAccess children
"slice_expression" -> sliceToSubscriptAccess children
"type_assertion_expression" -> withDefaultInfo $ case children of
[a, b] -> S.TypeAssertion a b
rest -> S.Error rest
"type_conversion_expression" -> withDefaultInfo $ case children of
[a, b] -> S.TypeConversion a b
rest -> S.Error rest
-- TODO: Handle multiple var specs
"var_declaration" -> withDefaultInfo . S.Indexed =<< mapM toVarDecl children
"short_var_declaration" -> listToVarDecls children
"if_statement" -> toIfStatement children
"call_expression" -> withDefaultInfo $ case children of
[id] -> S.FunctionCall id []
rest -> S.Error rest
"const_declaration" -> toConsts children
"func_literal" -> withDefaultInfo $ case children of
[params, _, body] -> S.AnonymousFunction (toList $ unwrap params) (toList $ unwrap body)
rest -> S.Error rest
_ -> withDefaultInfo $ case children of
[] -> S.Leaf . toText $ slice range source
_ -> S.Indexed children
where
toExpression f = \case
[expr] -> f expr
rest -> S.Error rest
toSubscriptAccess = \case
[a, b] -> S.SubscriptAccess a b
rest -> S.Error rest
sliceToSubscriptAccess = \case
a : rest -> do
slice <- withRanges range Slice rest $ S.Fixed rest
withDefaultInfo $ S.SubscriptAccess a slice
rest -> withDefaultInfo $ S.Error rest
toIfStatement = \case
[clause, block] ->
withDefaultInfo $ S.If clause (toList $ unwrap block)
[expr, block, elseBlock] | category (extract block) == Other "block" ->
withDefaultInfo $ S.If expr (toList (unwrap block) <> toList (unwrap elseBlock))
[expr, clause, block] -> do
clause' <- withRanges range If [expr, clause] (S.Indexed [expr, clause])
withDefaultInfo $ S.If clause' (toList $ unwrap block)
rest -> withCategory Error (S.Error rest)
toImports imports = do
imports' <- mapM toImport imports
withDefaultInfo $ S.Indexed (mconcat imports')
where
toImport i = case toList (unwrap i) of
[importName] -> sequenceA [ withCategory Import (S.Import importName []) ]
xs@(_:_) -> sequenceA [ withCategory Error (S.Error xs)]
[] -> pure []
toVarDecl varSpec = listToVarDecls (toList $ unwrap varSpec)
listToVarDecls list = case list of
[idList, exprs] | category (extract exprs) == Other "expression_list" -> do
assignments' <- sequenceA $ zipWith (\id expr -> withDefaultInfo $ S.VarAssignment id expr) (toList $ unwrap idList) (toList $ unwrap exprs)
withDefaultInfo (S.Indexed assignments')
[idList, _, exprs] -> do
assignments' <- sequenceA $ zipWith (\id expr -> withDefaultInfo $ S.VarAssignment id expr) (toList $ unwrap idList) (toList $ unwrap exprs)
withDefaultInfo (S.Indexed assignments')
idList : _ -> do
varDecls <- mapM (withDefaultInfo . S.VarDecl) (toList $ unwrap idList)
withDefaultInfo (S.Indexed varDecls)
_ -> withCategory Error (S.Error list)
toConsts constSpecs = do
assignments' <- sequenceA $ toVarAssignment <$> constSpecs
withDefaultInfo (S.Indexed assignments')
toVarAssignment constSpec =
case toList (unwrap constSpec) of
[idList, expressionList] -> do
assignments' <- sequenceA $ zipWith (\id expr -> withDefaultInfo $ S.VarAssignment id expr) (toList $ unwrap idList) (toList $ unwrap expressionList)
withDefaultInfo (S.Indexed assignments')
[idList, _, expressionList] -> do
assignments' <- sequenceA $ zipWith (\id expr -> withDefaultInfo $ S.VarAssignment id expr) (toList $ unwrap idList) (toList $ unwrap expressionList)
withDefaultInfo (S.Indexed assignments')
[idList] -> do
varDecls <- mapM (withDefaultInfo . S.VarDecl) (toList $ unwrap idList)
withDefaultInfo (S.Indexed varDecls)
rest -> withCategory Error (S.Error rest)
withRanges originalRange category' terms syntax = do
let ranges' = getField . extract <$> terms
sourceSpan' <- sourceSpan
let sourceSpans' = getField . extract <$> terms
pure $! cofree ((unionRangesFrom originalRange ranges' .: category' .: unionSourceSpansFrom sourceSpan' sourceSpans' .: RNil) :< syntax)
withCategory category syntax = do
sourceSpan' <- sourceSpan
pure $! cofree ((range .: category .: sourceSpan' .: RNil) :< syntax)
withDefaultInfo = withCategory (categoryForGoName name)
categoryForGoName :: Text -> Category
categoryForGoName = \case
"identifier" -> Identifier
"int_literal" -> NumberLiteral
"comment" -> Comment
"return_statement" -> Return
"interpreted_string_literal" -> StringLiteral
"raw_string_literal" -> StringLiteral
"binary_expression" -> RelationalOperator
"function_declaration" -> Function
"func_literal" -> AnonymousFunction
"call_expression" -> FunctionCall
"selector_expression" -> SubscriptAccess
"index_expression" -> SubscriptAccess
"slice_expression" -> SubscriptAccess
"parameters" -> Args
"short_var_declaration" -> VarDecl
"var_declaration" -> VarDecl
"var_spec" -> VarAssignment
"assignment_statement" -> Assignment
"source_file" -> Module
"const_declaration" -> VarDecl
"if_statement" -> If
"for_statement" -> For
"expression_switch_statement" -> Switch
"expression_case_clause" -> Case
"type_switch_statement" -> Switch
"type_case_clause" -> Case
"select_statement" -> Select
"communication_case" -> Case
"defer_statement" -> Defer
"go_statement" -> Go
"type_assertion_expression" -> TypeAssertion
"type_conversion_expression" -> TypeConversion
s -> Other (toS s)

View File

@ -41,21 +41,20 @@ termConstructor source sourceSpan name range children
S.Indexed rest -> S.Indexed $ a : rest
_ -> S.Indexed children
("comma_op", _ ) -> S.Error children
("function_call", _) -> case runCofree <$> children of
[ _ :< S.MemberAccess{..}, _ :< S.Args args ] -> S.MethodCall memberId property args
[ _ :< S.MemberAccess{..} ] -> S.MethodCall memberId property []
[ function, _ :< S.Args args ] -> S.FunctionCall (cofree function) args
(x:xs) -> S.FunctionCall (cofree x) (cofree <$> xs)
("function_call", _) -> case children of
member : args | category (extract member) == MemberAccess -> case toList (unwrap member) of
[target, method] -> S.MethodCall target method (toList . unwrap =<< args)
_ -> S.Error children
function : args -> S.FunctionCall function (toList . unwrap =<< args)
_ -> S.Error children
("ternary", condition : cases) -> S.Ternary condition cases
("ternary", _ ) -> S.Error children
("arguments", _) -> S.Args children
("var_assignment", [ x, y ]) -> S.VarAssignment x y
("var_assignment", _ ) -> S.Error children
("var_declaration", _) -> S.Indexed $ toVarDecl <$> children
("switch_statement", expr : rest) -> S.Switch expr rest
("switch_statement", _ ) -> S.Error children
("case", [ expr, body ]) -> S.Case expr body
("case", [ expr, body ]) -> S.Case expr [body]
("case", _ ) -> S.Error children
("object", _) -> S.Object $ foldMap toTuple children
("pair", _) -> S.Fixed children
@ -70,13 +69,14 @@ termConstructor source sourceSpan name range children
("throw_statment", _ ) -> S.Error children
("new_expression", [ expr ]) -> S.Constructor expr
("new_expression", _ ) -> S.Error children
("try_statement", [ body ]) -> S.Try body Nothing Nothing
("try_statement", [ body, catch ]) | Catch <- category (extract catch) -> S.Try body (Just catch) Nothing
("try_statement", [ body, finally ]) | Finally <- category (extract finally) -> S.Try body Nothing (Just finally)
("try_statement", [ body, catch, finally ])
| Catch <- category (extract catch)
, Finally <- category (extract finally) -> S.Try body (Just catch) (Just finally)
("try_statement", _ ) -> S.Error children
("try_statement", _) -> case children of
[ body ] -> S.Try [body] [] Nothing Nothing
[ body, catch ] | Catch <- category (extract catch) -> S.Try [body] [catch] Nothing Nothing
[ body, finally ] | Finally <- category (extract finally) -> S.Try [body] [] Nothing (Just finally)
[ body, catch, finally ]
| Catch <- category (extract catch)
, Finally <- category (extract finally) -> S.Try [body] [catch] Nothing (Just finally)
_ -> S.Error children
("array", _) -> S.Array children
("method_definition", [ identifier, params, exprs ]) -> S.Method identifier (toList (unwrap params)) (toList (unwrap exprs))
("method_definition", [ identifier, exprs ]) -> S.Method identifier [] (toList (unwrap exprs))

View File

@ -2,6 +2,7 @@
module Language.Ruby where
import Data.Record
import Data.List (partition)
import Info
import Prologue
import Source
@ -10,7 +11,7 @@ import qualified Syntax as S
import Term
operators :: [Text]
operators = ["and", "boolean_and", "or", "boolean_or", "bitwise_or", "bitwise_and", "shift", "relational", "comparison"]
operators = [ "and", "boolean_and", "or", "boolean_or", "bitwise_or", "bitwise_and", "shift", "relational", "comparison" ]
functions :: [Text]
functions = [ "lambda_literal", "lambda_expression" ]
@ -24,59 +25,104 @@ termConstructor
-> IO (Term (S.Syntax Text) (Record '[Range, Category, SourceSpan])) -- ^ The resulting term, in IO.
termConstructor source sourceSpan name range children
| name == "ERROR" = withDefaultInfo (S.Error children)
| name == "unless_modifier" = case children of
[ lhs, rhs ] -> do
condition <- withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)
withDefaultInfo $ S.If condition [lhs]
_ -> withDefaultInfo $ S.Error children
| name == "unless_statement" = case children of
( expr : rest ) -> do
condition <- withRecord (setCategory (extract expr) Negate) (S.Negate expr)
withDefaultInfo $ S.If condition rest
_ -> withDefaultInfo $ S.Error children
| name == "until_modifier" = case children of
[ lhs, rhs ] -> do
condition <- withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)
withDefaultInfo $ S.While condition [lhs]
_ -> withDefaultInfo $ S.Error children
| name == "until_statement" = case children of
( expr : rest ) -> do
condition <- withRecord (setCategory (extract expr) Negate) (S.Negate expr)
withDefaultInfo $ S.While condition rest
_ -> withDefaultInfo $ S.Error children
| otherwise = withDefaultInfo $ case (name, children) of
("argument_list", _) -> S.Args children
("array", _) -> S.Array children
("argument_pair", [ k, v ] ) -> S.Pair k v
("argument_pair", _ ) -> S.Error children
("keyword_parameter", [ k, v ] ) -> S.Pair k v
-- NB: ("keyword_parameter", k) is a required keyword parameter, e.g.:
-- def foo(name:); end
-- Let it fall through to generate an Indexed syntax.
("optional_parameter", [ k, v ] ) -> S.Pair k v
("optional_parameter", _ ) -> S.Error children
("array", _ ) -> S.Array children
("assignment", [ identifier, value ]) -> S.Assignment identifier value
("assignment", _ ) -> S.Error children
("case_statement", expr : rest) -> S.Switch expr rest
("begin_statement", _ ) -> case partition (\x -> category (extract x) == Rescue) children of
(rescues, rest) -> case partition (\x -> category (extract x) == Ensure || category (extract x) == Else) rest of
(ensureElse, body) -> case ensureElse of
[ elseBlock, ensure ]
| Else <- category (extract elseBlock)
, Ensure <- category (extract ensure) -> S.Try body rescues (Just elseBlock) (Just ensure)
[ ensure, elseBlock ]
| Ensure <- category (extract ensure)
, Else <- category (extract elseBlock) -> S.Try body rescues (Just elseBlock) (Just ensure)
[ elseBlock ] | Else <- category (extract elseBlock) -> S.Try body rescues (Just elseBlock) Nothing
[ ensure ] | Ensure <- category (extract ensure) -> S.Try body rescues Nothing (Just ensure)
_ -> S.Try body rescues Nothing Nothing
("case_statement", expr : body ) -> S.Switch expr body
("case_statement", _ ) -> S.Error children
("when_block", condition : body ) -> S.Case condition body
("when_block", _ ) -> S.Error children
("class_declaration", [ identifier, superclass, definitions ]) -> S.Class identifier (Just superclass) (toList (unwrap definitions))
("class_declaration", [ identifier, definitions ]) -> S.Class identifier Nothing (toList (unwrap definitions))
("class_declaration", _ ) -> S.Error children
("comment", _) -> S.Comment . toText $ slice range source
("comment", _ ) -> S.Comment . toText $ slice range source
("conditional_assignment", [ identifier, value ]) -> S.ConditionalAssignment identifier value
("conditional_assignment", _ ) -> S.Error children
("conditional", condition : cases) -> S.Ternary condition cases
("conditional", _ ) -> S.Error children
("function_call", _) -> case runCofree <$> children of
[ _ :< S.MemberAccess{..}, _ :< S.Args args ] -> S.MethodCall memberId property args
[ _ :< S.MemberAccess{..} ] -> S.MethodCall memberId property []
[ function, _ :< S.Args args ] -> S.FunctionCall (cofree function) args
(x:xs) -> S.FunctionCall (cofree x) (cofree <$> xs)
("function_call", _ ) -> case children of
member : args | MemberAccess <- category (extract member) -> case toList (unwrap member) of
[target, method] -> S.MethodCall target method (toList . unwrap =<< args)
_ -> S.Error children
function : args -> S.FunctionCall function (toList . unwrap =<< args)
_ -> S.Error children
("hash", _) -> S.Object $ foldMap toTuple children
("hash", _ ) -> S.Object $ foldMap toTuple children
("if_modifier", [ lhs, condition ]) -> S.If condition [lhs]
("if_modifier", _ ) -> S.Error children
("if_statement", expr : rest ) -> S.If expr rest
("if_statement", condition : body ) -> S.If condition body
("if_statement", _ ) -> S.Error children
("elsif_block", condition : body ) -> S.If condition body
("elsif_block", _ ) -> S.Error children
("element_reference", [ base, element ]) -> S.SubscriptAccess base element
("element_reference", _ ) -> S.Error children
("for_statement", lhs : expr : rest ) -> S.For [lhs, expr] rest
("for_statement", _ ) -> S.Error children
("math_assignment", [ identifier, value ]) -> S.MathAssignment identifier value
("math_assignment", _ ) -> S.Error children
("member_access", [ base, property ]) -> S.MemberAccess base property
("member_access", _ ) -> S.Error children
("method_declaration", [ identifier, params, exprs ]) -> S.Method identifier (toList (unwrap params)) (toList (unwrap exprs))
("method_declaration", [ identifier, exprs ]) -> S.Method identifier [] (toList (unwrap exprs))
("method_declaration", _ ) -> S.Error children
("method_declaration", _ ) -> case children of
identifier : params : body | Params <- category (extract params) -> S.Method identifier (toList (unwrap params)) body
identifier : body -> S.Method identifier [] body
_ -> S.Error children
("module_declaration", identifier : body ) -> S.Module identifier body
("module_declaration", _ ) -> S.Error children
("rescue_block", _ ) -> case children of
args : lastException : rest
| RescueArgs <- category (extract args)
, RescuedException <- category (extract lastException) -> S.Rescue (toList (unwrap args) <> [lastException]) rest
lastException : rest | RescuedException <- category (extract lastException) -> S.Rescue [lastException] rest
args : body | RescueArgs <- category (extract args) -> S.Rescue (toList (unwrap args)) body
body -> S.Rescue [] body
("rescue_modifier", [lhs, rhs] ) -> S.Rescue [lhs] [rhs]
("rescue_modifier", _ ) -> S.Error children
("return_statement", _ ) -> S.Return (listToMaybe children)
("unless_modifier", [ lhs, condition ]) -> S.Unless condition [lhs]
("unless_modifier", _ ) -> S.Error children
("unless_statement", expr : rest ) -> S.Unless expr rest
("unless_statement", _ ) -> S.Error children
("until_modifier", [ lhs, condition ]) -> S.Until condition [lhs]
("until_modifier", _ ) -> S.Error children
("until_statement", expr : rest ) -> S.Until expr rest
("until_statement", _ ) -> S.Error children
("while_modifier", [ lhs, condition ]) -> S.While condition [lhs]
("while_modifier", _ ) -> S.Error children
("while_statement", expr : rest ) -> S.While expr rest
("while_statement", _ ) -> S.Error children
("yield", _) -> S.Yield (listToMaybe children)
("for_statement", lhs : expr : rest ) -> S.For [lhs, expr] rest
("for_statement", _ ) -> S.Error children
("yield", _ ) -> S.Yield (listToMaybe children)
_ | name `elem` operators -> S.Operator children
_ | name `elem` functions -> case children of
[ body ] -> S.AnonymousFunction [] [body]
@ -85,65 +131,77 @@ termConstructor source sourceSpan name range children
(_, []) -> S.Leaf . toText $ slice range source
_ -> S.Indexed children
where
withDefaultInfo syntax = do
withRecord record syntax = pure $! cofree (record :< syntax)
withCategory category syntax = do
sourceSpan' <- sourceSpan
pure $! cofree ((range .: categoryForRubyName name .: sourceSpan' .: RNil) :< syntax)
pure $! cofree ((range .: category .: sourceSpan' .: RNil) :< syntax)
withDefaultInfo syntax = case syntax of
S.MethodCall{} -> withCategory MethodCall syntax
_ -> withCategory (categoryForRubyName name) syntax
categoryForRubyName :: Text -> Category
categoryForRubyName = \case
"and" -> BooleanOperator
"argument_list" -> Args
"argument_pair" -> ArgumentPair
"array" -> ArrayLiteral
"assignment" -> Assignment
"begin_statement" -> ExpressionStatements
"begin_statement" -> 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" -> Switch
"case_statement" -> Case
"class_declaration" -> Class
"comment" -> Comment
"comparison" -> RelationalOperator -- comparison operator, e.g. <, <=, >=, >.
"conditional_assignment" -> ConditionalAssignment
"conditional" -> Ternary
"element_reference" -> SubscriptAccess
"else_block" -> ExpressionStatements
"elsif_block" -> ExpressionStatements
"ensure_block" -> ExpressionStatements
"else_block" -> Else
"elsif_block" -> Elsif
"ensure_block" -> Ensure
"ERROR" -> Error
"float" -> NumberLiteral
"for_statement" -> For
"formal_parameters" -> Params
"function_call" -> FunctionCall
"function" -> Function
"hash_splat_parameter" -> HashSplatParameter
"hash" -> Object
"identifier" -> Identifier
"if_modifier" -> If
"if_statement" -> If
"integer" -> IntegerLiteral
"interpolation" -> Interpolation
"keyword_parameter" -> KeywordParameter
"math_assignment" -> MathAssignment
"member_access" -> MemberAccess
"method_declaration" -> Method
"module_declaration" -> Module
"nil" -> Identifier
"optional_parameter" -> OptionalParameter
"or" -> BooleanOperator
"program" -> Program
"regex" -> Regex
"relational" -> RelationalOperator -- relational operator, e.g. ==, !=, ===, <=>, =~, !~.
"rescue_block" -> ExpressionStatements
"rescue_arguments" -> RescueArgs
"rescue_block" -> Rescue
"rescue_modifier" -> RescueModifier
"rescued_exception" -> RescuedException
"return_statement" -> Return
"shift" -> BitwiseOperator -- bitwise shift, e.g <<, >>.
"splat_parameter" -> SplatParameter
"string" -> StringLiteral
"subshell" -> Subshell
"symbol" -> SymbolLiteral
"then_block" -> ExpressionStatements
"unless_modifier" -> Unless
"unless_statement" -> Unless
"until_modifier" -> Until
"until_statement" -> Until
"when_block" -> ExpressionStatements
"when_block" -> When
"while_modifier" -> While
"while_statement" -> While
"yield" -> Yield

View File

@ -66,6 +66,7 @@ parserForType mediaType = case languageForType mediaType of
Just JavaScript -> treeSitterParser JavaScript ts_language_javascript
Just Markdown -> cmarkParser
Just Ruby -> treeSitterParser Ruby ts_language_ruby
Just Language.Go -> treeSitterParser Language.Go ts_language_go
_ -> lineByLineParser
-- | Decorate a 'Term' using a function to compute the annotation values at every node.
@ -97,6 +98,10 @@ lineByLineParser SourceBlob{..} = pure . cofree . root $ case foldl' annotateLea
(accum <> [ leaf charIndex (toText line) ] , charIndex + length line)
toText = T.pack . Source.toString
-- | Return the parser that should be used for a given path.
parserForFilepath :: FilePath -> Parser (Syntax Text) (Record '[Cost, Range, Category, SourceSpan])
parserForFilepath path blob = decorateTerm termCostDecorator <$> parserForType (toS (takeExtension path)) blob
-- | Read the file and convert it to Unicode.
readAndTranscodeFile :: FilePath -> IO (Source Char)
readAndTranscodeFile path = do

View File

@ -101,7 +101,6 @@ syntaxToTermField syntax = case syntax of
S.MathAssignment identifier value -> [ "identifier" .= identifier ] <> [ "value" .= value ]
S.MemberAccess identifier value -> [ "identifier" .= identifier ] <> [ "value" .= value ]
S.MethodCall identifier methodIdentifier parameters -> [ "identifier" .= identifier ] <> [ "methodIdentifier" .= methodIdentifier ] <> [ "parameters" .= parameters ]
S.Args c -> childrenFields c
S.Operator syntaxes -> [ "operatorSyntaxes" .= syntaxes ]
S.VarDecl declaration -> [ "declaration" .= declaration ]
S.VarAssignment identifier value -> [ "identifier" .= identifier ] <> [ "value" .= value ]
@ -119,7 +118,7 @@ syntaxToTermField syntax = case syntax of
S.Return expression -> [ "expression" .= expression ]
S.Throw c -> [ "expression" .= c ]
S.Constructor expression -> [ "expression" .= expression ]
S.Try body catchExpression finallyExpression -> [ "body" .= body ] <> [ "catchExpression" .= catchExpression ] <> [ "finallyExpression" .= finallyExpression ]
S.Try body catchExpression elseExpression finallyExpression -> [ "body" .= body ] <> [ "catchExpression" .= catchExpression ] <> [ "elseExpression" .= elseExpression ] <> [ "finallyExpression" .= finallyExpression ]
S.Array c -> childrenFields c
S.Class identifier superclass definitions -> [ "identifier" .= identifier ] <> [ "superclass" .= superclass ] <> [ "definitions" .= definitions ]
S.Method identifier parameters definitions -> [ "identifier" .= identifier ] <> [ "parameters" .= parameters ] <> [ "definitions" .= definitions ]
@ -129,6 +128,11 @@ syntaxToTermField syntax = case syntax of
S.Export identifier statements -> [ "identifier" .= identifier ] <> [ "statements" .= statements ]
S.ConditionalAssignment id value -> [ "conditionalIdentifier" .= id ] <> [ "value" .= value ]
S.Yield expr -> [ "yieldExpression" .= expr ]
S.Until expr body -> [ "untilExpr" .= expr ] <> [ "untilBody" .= body ]
S.Unless expr clauses -> [ "unless" .= expr ] <> childrenFields clauses
S.Negate expr -> [ "negate" .= expr ]
S.Rescue args expressions -> [ "args" .= args ] <> childrenFields expressions
S.Select cases -> childrenFields cases
S.Go cases -> childrenFields cases
S.Defer cases -> childrenFields cases
S.TypeAssertion a b -> childrenFields [a, b]
S.TypeConversion a b -> childrenFields [a, b]
where childrenFields c = [ "children" .= c ]

View File

@ -57,7 +57,7 @@ styleName category = "category-" <> case category of
TemplateString -> "template_string"
Regex -> "regex"
Identifier -> "identifier"
Params -> "parameters"
C.Params -> "parameters"
ExpressionStatements -> "expression_statements"
C.MathAssignment -> "math_assignment"
C.SubscriptAccess -> "subscript_access"
@ -83,12 +83,35 @@ styleName category = "category-" <> case category of
C.Module -> "module_statement"
C.Import -> "import_statement"
C.Export -> "export_statement"
C.AnonymousFunction -> "anonymous_function"
C.Interpolation -> "interpolation"
C.Subshell -> "subshell"
C.ConditionalAssignment -> "conditional_assignment"
C.Yield -> "yield_statement"
C.Until -> "until"
C.Unless -> "unless_statement"
C.Begin -> "begin_statement"
C.Else -> "else_block"
C.Elsif -> "elsif_block"
C.Ensure -> "ensure_block"
C.Rescue -> "rescue_block"
C.RescueModifier -> "rescue_modifier"
C.When -> "when_block"
C.RescuedException -> "last_exception"
C.RescueArgs -> "rescue_args"
C.Negate -> "negate"
C.Select -> "select_statement"
C.Go -> "go_statement"
C.Defer -> "defer_statement"
C.Slice -> "slice_expression"
C.TypeAssertion -> "type_assertion"
C.TypeConversion -> "type_conversion"
C.ArgumentPair -> "argument_pair"
C.KeywordParameter -> "keyword_param"
C.OptionalParameter -> "optional_param"
C.SplatParameter -> "splat_param"
C.HashSplatParameter -> "hash_splat_param"
C.BlockParameter -> "block_param"
-- | Pick the class name for a split patch.
splitPatchToClassName :: SplitPatch a -> AttributeValue

View File

@ -12,6 +12,7 @@ import qualified Data.Aeson as A
import Test.QuickCheck
import Data.These
import Data.Text.Arbitrary()
import Data.Semigroup
-- |
-- Source position information
@ -54,6 +55,24 @@ displayStartEndPos :: SourceSpan -> Text
displayStartEndPos sp =
displaySourcePos (spanStart sp) <> " - " <> displaySourcePos (spanEnd sp)
unionSourceSpansFrom :: Foldable f => SourceSpan -> f SourceSpan -> SourceSpan
unionSourceSpansFrom sourceSpan = fromMaybe sourceSpan . maybeConcat
maybeConcat :: (Foldable f, Semigroup a) => f a -> Maybe a
maybeConcat = getOption . foldMap (Option . Just)
unionSourceSpans :: Foldable f => f SourceSpan -> SourceSpan
unionSourceSpans = unionSourceSpansFrom emptySourceSpan
unionSourceSpan :: SourceSpan -> SourceSpan -> SourceSpan
unionSourceSpan (SourceSpan start1 end1) (SourceSpan start2 end2) = SourceSpan (min start1 start2) (max end1 end2)
emptySourceSpan :: SourceSpan
emptySourceSpan = SourceSpan (SourcePos 1 1) (SourcePos 1 1)
instance Semigroup SourceSpan where
a <> b = unionSourceSpan a b
instance A.ToJSON SourceSpan where
toJSON SourceSpan{..} =
A.object [ "start" .= spanStart

View File

@ -36,9 +36,6 @@ data Syntax a f
-- | A method call consisting of its target, the method name, and the parameters passed to the method.
-- | e.g. in Javascript console.log('hello') represents a method call.
| MethodCall { targetId :: f, methodId :: f, methodParams :: [f] }
-- | The list of arguments to a method call.
-- | TODO: It might be worth removing this and using Fixed instead.
| Args [f]
-- | An operator can be applied to a list of syntaxes.
| Operator [f]
-- | A variable declaration. e.g. var foo;
@ -49,7 +46,8 @@ data Syntax a f
-- | e.g. in Javascript x["y"] represents a subscript access syntax.
| SubscriptAccess { subscriptId :: f, subscriptElement :: f }
| Switch { switchExpr :: f, cases :: [f] }
| Case { caseExpr :: f, caseStatements :: f }
| Case { caseExpr :: f, caseStatements :: [f] }
| Select { cases :: [f] }
| Object { keyValues :: [f] }
-- | A pair in an Object. e.g. foo: bar or foo => bar
| Pair f f
@ -65,7 +63,8 @@ data Syntax a f
| Return (Maybe f)
| Throw f
| Constructor f
| Try f (Maybe f) (Maybe f)
-- | TODO: Is it a problem that in Ruby, this pattern can work for method def too?
| Try { tryBegin :: [f], catchRescue :: [f], beginElse :: Maybe f, finallyEnsure :: Maybe f }
-- | An array literal with list of children.
| Array [f]
-- | A class with an identifier, superclass, and a list of definitions.
@ -81,9 +80,14 @@ data Syntax a f
-- | A conditional assignment represents expressions whose operator classifies as conditional (e.g. ||= or &&=).
| ConditionalAssignment { conditionalAssignmentId :: f, value :: f }
| Yield (Maybe f)
| Until { untilExpr :: f, untilBody :: [f] }
-- | An unless statement with an expression and maybe more expression clauses.
| Unless f [f]
-- | A negation of a single expression.
| Negate f
-- | A rescue block has a list of arguments to rescue and a list of expressions.
| Rescue [f] [f]
| Go f
| Defer f
| TypeAssertion f f
| TypeConversion f f
deriving (Eq, Foldable, Functor, Generic, Generic1, Mergeable, Ord, Show, Traversable, ToJSON)

View File

@ -10,20 +10,21 @@ import Data.Record
import Data.These
import Syntax
-- | An annotated node (Syntax) in an abstract syntax tree.
-- | A Term with an abstract syntax tree and an annotation.
type Term f annotation = Cofree f annotation
type TermF = CofreeF
type Term f = Cofree f
type SyntaxTermF leaf fields = TermF (Syntax leaf) (Record fields)
-- | A Term with a Syntax leaf and a record of fields.
type SyntaxTerm leaf fields = Term (Syntax leaf) (Record fields)
type SyntaxTermF leaf fields = TermF (Syntax leaf) (Record fields)
-- Term has a Base functor TermF which gives it Recursive and Corecursive instances.
type instance Base (Term f a) = TermF f a
instance Functor f => Recursive (Term f a) where project = runCofree
instance Functor f => Corecursive (Term f a) where embed = cofree
-- | Zip two terms by combining their annotations into a pair of annotations.
-- | If the structure of the two terms don't match, then Nothing will be returned.
zipTerms :: (Traversable f, GAlign f) => Term f annotation -> Term f annotation -> Maybe (Term f (Both annotation))
zipTerms t1 t2 = iter go (alignCofreeWith galign (const Nothing) both (These t1 t2))
where go (a :< s) = cofree . (a :<) <$> sequenceA s

View File

@ -5,8 +5,9 @@ import Prologue hiding (Constructor)
import Category
import Data.Record
import Language
import qualified Language.JavaScript as JS
import qualified Language.C as C
import qualified Language.Go as Go
import qualified Language.JavaScript as JS
import qualified Language.Ruby as Ruby
import Parser
import Range
@ -58,6 +59,7 @@ documentToTerm language document SourceBlob{..} = alloca $ \ root -> do
termConstructor = case language of
JavaScript -> JS.termConstructor
C -> C.termConstructor
Language.Go -> Go.termConstructor
Ruby -> Ruby.termConstructor
_ -> Language.termConstructor
isNonEmpty child = category (extract child) /= Empty

View File

@ -2,6 +2,7 @@ module IntegrationFormatSpec where
import Arguments
import Data.Aeson
import Data.List.Split
import Control.Exception
import qualified Data.ByteString.Lazy as DL
import JSONTestCase
@ -21,10 +22,11 @@ catchException = handle errorHandler
assertDiffSummary :: JSONTestCase -> Format -> (Either String ExpectedResult -> Either String ExpectedResult -> Expectation) -> Expectation
assertDiffSummary JSONTestCase {..} format matcher = do
diffs <- fetchDiffs $ args gitDir sha1 sha2 filePaths format
diffs <- fetchDiffs $ args gitDir (Prelude.head shas') (Prelude.last shas') filePaths format
result <- catchException . pure . pure . concatOutputs $ diffs
let actual = eitherDecode . DL.fromStrict . encodeUtf8 . fromJust . listToMaybe $ result
matcher actual (Right expectedResult)
where shas' = splitOn ".." shas
runTestsIn :: [FilePath] -> Format -> (Either String ExpectedResult -> Either String ExpectedResult -> Expectation) -> SpecWith ()
runTestsIn filePaths format matcher = do

View File

@ -12,9 +12,11 @@ data JSONMetaRepo = JSONMetaRepo { repoUrl :: !String
, language :: !String
, fileExt :: !String
, syntaxes :: ![JSONMetaSyntax]
, templateText :: !(Maybe String)
} deriving (Show, Generic, FromJSON)
data JSONMetaSyntax = JSONMetaSyntax { syntax :: !String
data JSONMetaSyntax = JSONMetaSyntax { template :: !(Maybe String)
, syntax :: !String
, insert :: !String
, replacement :: !String
} deriving (Show, Generic, FromJSON)
@ -22,8 +24,8 @@ data JSONMetaSyntax = JSONMetaSyntax { syntax :: !String
data JSONTestCase = JSONTestCase { gitDir :: !String
, testCaseDescription :: !String
, filePaths :: ![String]
, sha1 :: !String
, sha2 :: !String
, shas :: !String
, patch :: ![String]
, expectedResult :: !ExpectedResult
} deriving (Show, Generic, FromJSON)

View File

@ -9,9 +9,9 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "c57d91166c3246b8e352252024dc21de6a42f707",
"patch": [],
"gitDir": "test/corpus/repos/javascript",
"sha2": "244097ce5a74d6275f249d5159a6a14696a1eddf"
"shas": "c57d91166c3246b8e352252024dc21de6a42f707..244097ce5a74d6275f249d5159a6a14696a1eddf"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-test",
@ -24,7 +24,7 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "244097ce5a74d6275f249d5159a6a14696a1eddf",
"patch": [],
"gitDir": "test/corpus/repos/javascript",
"sha2": "0abfc815d9c5912259cfc25becb398a8f1444d40"
"shas": "244097ce5a74d6275f249d5159a6a14696a1eddf..0abfc815d9c5912259cfc25becb398a8f1444d40"
}]

View File

@ -9,9 +9,9 @@
"filePaths": [
"relational-operator.js"
],
"sha1": "f79a619c0277b82bb45cb1510847b78ba44ea31b",
"patch": [],
"gitDir": "test/corpus/repos/javascript",
"sha2": "1fc7441b1fb64b171cf7892e3ce25bc55e25d754"
"shas": "f79a619c0277b82bb45cb1510847b78ba44ea31b..1fc7441b1fb64b171cf7892e3ce25bc55e25d754"
}
,{
"testCaseDescription": "javascript-relational-operator-replacement-test",
@ -24,7 +24,7 @@
"filePaths": [
"relational-operator.js"
],
"sha1": "1fc7441b1fb64b171cf7892e3ce25bc55e25d754",
"patch": [],
"gitDir": "test/corpus/repos/javascript",
"sha2": "e1d768da1e35b8066276dc5b5f9653442345948d"
"shas": "1fc7441b1fb64b171cf7892e3ce25bc55e25d754..e1d768da1e35b8066276dc5b5f9653442345948d"
}]

View File

@ -1,241 +0,0 @@
[{
"testCaseDescription": "ruby-control-statements-insert-test",
"expectedResult": {
"changes": {
"control-statements.rb": [
{
"span": {
"insert": {
"start": [
2,
2
],
"end": [
2,
5
]
}
},
"summary": "Added a begin block"
}
]
},
"errors": {}
},
"filePaths": [
"control-statements.rb"
],
"sha1": "0afd2cfcf489061cc131d9970716bb04bb5cb203",
"gitDir": "test/corpus/repos/ruby",
"sha2": "703d5515f05e02ad93d56987b520328f4a351265"
}
,{
"testCaseDescription": "ruby-control-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"control-statements.rb": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
2,
4
]
}
},
"summary": "Added a begin block"
}
]
},
"errors": {}
},
"filePaths": [
"control-statements.rb"
],
"sha1": "703d5515f05e02ad93d56987b520328f4a351265",
"gitDir": "test/corpus/repos/ruby",
"sha2": "554242b8ed778be509d72c90b71381c7a49c5bf4"
}
,{
"testCaseDescription": "ruby-control-statements-delete-insert-test",
"expectedResult": {
"changes": {
"control-statements.rb": [
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
2,
4
]
},
{
"start": [
2,
2
],
"end": [
2,
5
]
}
]
},
"summary": "Replaced a begin block with a begin block"
}
]
},
"errors": {}
},
"filePaths": [
"control-statements.rb"
],
"sha1": "554242b8ed778be509d72c90b71381c7a49c5bf4",
"gitDir": "test/corpus/repos/ruby",
"sha2": "bd0b46ca0ec2510b867cc5670fbafb0068db0d9c"
}
,{
"testCaseDescription": "ruby-control-statements-replacement-test",
"expectedResult": {
"changes": {
"control-statements.rb": [
{
"span": {
"replace": [
{
"start": [
2,
2
],
"end": [
2,
5
]
},
{
"start": [
1,
1
],
"end": [
2,
4
]
}
]
},
"summary": "Replaced a begin block with a begin block"
}
]
},
"errors": {}
},
"filePaths": [
"control-statements.rb"
],
"sha1": "bd0b46ca0ec2510b867cc5670fbafb0068db0d9c",
"gitDir": "test/corpus/repos/ruby",
"sha2": "3a174f29f8c703fdb1ebf05ef9ef856550f3b968"
}
,{
"testCaseDescription": "ruby-control-statements-delete-replacement-test",
"expectedResult": {
"changes": {
"control-statements.rb": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
2,
4
]
}
},
"summary": "Deleted a begin block"
}
]
},
"errors": {}
},
"filePaths": [
"control-statements.rb"
],
"sha1": "3a174f29f8c703fdb1ebf05ef9ef856550f3b968",
"gitDir": "test/corpus/repos/ruby",
"sha2": "5dc5bafea85edc0573668d9b80192e910150caf3"
}
,{
"testCaseDescription": "ruby-control-statements-delete-test",
"expectedResult": {
"changes": {
"control-statements.rb": [
{
"span": {
"delete": {
"start": [
8,
3
],
"end": [
8,
6
]
}
},
"summary": "Deleted the 'baz' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"control-statements.rb"
],
"sha1": "5dc5bafea85edc0573668d9b80192e910150caf3",
"gitDir": "test/corpus/repos/ruby",
"sha2": "8cde2cc96f0eef72794161e18540bbb43a24937d"
}
,{
"testCaseDescription": "ruby-control-statements-delete-rest-test",
"expectedResult": {
"changes": {
"control-statements.rb": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
2,
4
]
}
},
"summary": "Deleted a begin block"
}
]
},
"errors": {}
},
"filePaths": [
"control-statements.rb"
],
"sha1": "8cde2cc96f0eef72794161e18540bbb43a24937d",
"gitDir": "test/corpus/repos/ruby",
"sha2": "457dc7fc963751d0adf0ea4eb8934e39ef717e32"
}]

View File

@ -0,0 +1,815 @@
[{
"testCaseDescription": "go-array-types-insert-test",
"expectedResult": {
"changes": {
"array-types.go": [
{
"span": {
"insert": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
1,
9
],
"end": [
1,
10
]
}
},
"summary": "Added the '2'"
},
{
"span": {
"insert": {
"start": [
1,
11
],
"end": [
1,
12
]
}
},
"summary": "Added the '2'"
},
{
"span": {
"insert": {
"start": [
1,
13
],
"end": [
1,
14
]
}
},
"summary": "Added the 'x' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"array-types.go"
],
"patch": [
"diff --git a/array-types.go b/array-types.go",
"index e69de29..f9c11b8 100644",
"--- a/array-types.go",
"+++ b/array-types.go",
"@@ -0,0 +1 @@",
"+type a [2+2]x"
],
"gitDir": "test/corpus/repos/go",
"shas": "4605c9308ffc84f9d63dc5e62562b0461d53d5b9..e72a08882ea7900f125d452420494cdf0f9dd5e4"
}
,{
"testCaseDescription": "go-array-types-replacement-insert-test",
"expectedResult": {
"changes": {
"array-types.go": [
{
"span": {
"insert": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
1,
9
],
"end": [
1,
10
]
}
},
"summary": "Added the '1'"
},
{
"span": {
"insert": {
"start": [
1,
11
],
"end": [
1,
12
]
}
},
"summary": "Added the '1'"
},
{
"span": {
"insert": {
"start": [
1,
13
],
"end": [
1,
14
]
}
},
"summary": "Added the 'y' identifier"
},
{
"span": {
"insert": {
"start": [
2,
6
],
"end": [
2,
7
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
2,
9
],
"end": [
2,
10
]
}
},
"summary": "Added the '2'"
},
{
"span": {
"insert": {
"start": [
2,
11
],
"end": [
2,
12
]
}
},
"summary": "Added the '2'"
},
{
"span": {
"insert": {
"start": [
2,
13
],
"end": [
2,
14
]
}
},
"summary": "Added the 'x' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"array-types.go"
],
"patch": [
"diff --git a/array-types.go b/array-types.go",
"index f9c11b8..d2b8166 100644",
"--- a/array-types.go",
"+++ b/array-types.go",
"@@ -1 +1,3 @@",
"+type a [1+1]y",
"+type a [2+2]x",
" type a [2+2]x"
],
"gitDir": "test/corpus/repos/go",
"shas": "e72a08882ea7900f125d452420494cdf0f9dd5e4..aa6f10e79008f9c024ed3883cec3d84f74157628"
}
,{
"testCaseDescription": "go-array-types-delete-insert-test",
"expectedResult": {
"changes": {
"array-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
9
],
"end": [
1,
10
]
},
{
"start": [
1,
9
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced '1' with '2'"
},
{
"span": {
"replace": [
{
"start": [
1,
11
],
"end": [
1,
12
]
},
{
"start": [
1,
11
],
"end": [
1,
12
]
}
]
},
"summary": "Replaced '1' with '2'"
},
{
"span": {
"replace": [
{
"start": [
1,
13
],
"end": [
1,
14
]
},
{
"start": [
1,
13
],
"end": [
1,
14
]
}
]
},
"summary": "Replaced the 'y' identifier with the 'x' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"array-types.go"
],
"patch": [
"diff --git a/array-types.go b/array-types.go",
"index d2b8166..823c5f1 100644",
"--- a/array-types.go",
"+++ b/array-types.go",
"@@ -1,3 +1,3 @@",
"-type a [1+1]y",
"+type a [2+2]x",
" type a [2+2]x",
" type a [2+2]x"
],
"gitDir": "test/corpus/repos/go",
"shas": "aa6f10e79008f9c024ed3883cec3d84f74157628..e89c6cb69bfb749d230d2d02cb2f121098bb9ca7"
}
,{
"testCaseDescription": "go-array-types-replacement-test",
"expectedResult": {
"changes": {
"array-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
9
],
"end": [
1,
10
]
},
{
"start": [
1,
9
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced '2' with '1'"
},
{
"span": {
"replace": [
{
"start": [
1,
11
],
"end": [
1,
12
]
},
{
"start": [
1,
11
],
"end": [
1,
12
]
}
]
},
"summary": "Replaced '2' with '1'"
},
{
"span": {
"replace": [
{
"start": [
1,
13
],
"end": [
1,
14
]
},
{
"start": [
1,
13
],
"end": [
1,
14
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'y' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"array-types.go"
],
"patch": [
"diff --git a/array-types.go b/array-types.go",
"index 823c5f1..d2b8166 100644",
"--- a/array-types.go",
"+++ b/array-types.go",
"@@ -1,3 +1,3 @@",
"-type a [2+2]x",
"+type a [1+1]y",
" type a [2+2]x",
" type a [2+2]x"
],
"gitDir": "test/corpus/repos/go",
"shas": "e89c6cb69bfb749d230d2d02cb2f121098bb9ca7..cb40195715b97fd727f39a658f90da91280dfeb3"
}
,{
"testCaseDescription": "go-array-types-delete-replacement-test",
"expectedResult": {
"changes": {
"array-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
1,
9
],
"end": [
1,
10
]
}
},
"summary": "Deleted the '1'"
},
{
"span": {
"delete": {
"start": [
1,
11
],
"end": [
1,
12
]
}
},
"summary": "Deleted the '1'"
},
{
"span": {
"delete": {
"start": [
1,
13
],
"end": [
1,
14
]
}
},
"summary": "Deleted the 'y' identifier"
},
{
"span": {
"delete": {
"start": [
2,
6
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
2,
9
],
"end": [
2,
10
]
}
},
"summary": "Deleted the '2'"
},
{
"span": {
"delete": {
"start": [
2,
11
],
"end": [
2,
12
]
}
},
"summary": "Deleted the '2'"
},
{
"span": {
"delete": {
"start": [
2,
13
],
"end": [
2,
14
]
}
},
"summary": "Deleted the 'x' identifier"
},
{
"span": {
"insert": {
"start": [
2,
6
],
"end": [
2,
7
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
2,
9
],
"end": [
2,
10
]
}
},
"summary": "Added the '1'"
},
{
"span": {
"insert": {
"start": [
2,
11
],
"end": [
2,
12
]
}
},
"summary": "Added the '1'"
},
{
"span": {
"insert": {
"start": [
2,
13
],
"end": [
2,
14
]
}
},
"summary": "Added the 'y' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"array-types.go"
],
"patch": [
"diff --git a/array-types.go b/array-types.go",
"index d2b8166..5b93d14 100644",
"--- a/array-types.go",
"+++ b/array-types.go",
"@@ -1,3 +1,2 @@",
"-type a [1+1]y",
"-type a [2+2]x",
" type a [2+2]x",
"+type a [1+1]y"
],
"gitDir": "test/corpus/repos/go",
"shas": "cb40195715b97fd727f39a658f90da91280dfeb3..9629b178034aa4530628081bc407e1c9009fe13d"
}
,{
"testCaseDescription": "go-array-types-delete-test",
"expectedResult": {
"changes": {
"array-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
1,
9
],
"end": [
1,
10
]
}
},
"summary": "Deleted the '2'"
},
{
"span": {
"delete": {
"start": [
1,
11
],
"end": [
1,
12
]
}
},
"summary": "Deleted the '2'"
},
{
"span": {
"delete": {
"start": [
1,
13
],
"end": [
1,
14
]
}
},
"summary": "Deleted the 'x' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"array-types.go"
],
"patch": [
"diff --git a/array-types.go b/array-types.go",
"index 5b93d14..967447e 100644",
"--- a/array-types.go",
"+++ b/array-types.go",
"@@ -1,2 +1 @@",
"-type a [2+2]x",
" type a [1+1]y"
],
"gitDir": "test/corpus/repos/go",
"shas": "9629b178034aa4530628081bc407e1c9009fe13d..d9b4ebb8d64c12b8efbc1fbdcc2c31bf584a17c2"
}
,{
"testCaseDescription": "go-array-types-delete-rest-test",
"expectedResult": {
"changes": {
"array-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
1,
9
],
"end": [
1,
10
]
}
},
"summary": "Deleted the '1'"
},
{
"span": {
"delete": {
"start": [
1,
11
],
"end": [
1,
12
]
}
},
"summary": "Deleted the '1'"
},
{
"span": {
"delete": {
"start": [
1,
13
],
"end": [
1,
14
]
}
},
"summary": "Deleted the 'y' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"array-types.go"
],
"patch": [
"diff --git a/array-types.go b/array-types.go",
"index 967447e..e69de29 100644",
"--- a/array-types.go",
"+++ b/array-types.go",
"@@ -1 +0,0 @@",
"-type a [1+1]y"
],
"gitDir": "test/corpus/repos/go",
"shas": "d9b4ebb8d64c12b8efbc1fbdcc2c31bf584a17c2..ecbb5b13e89407c4e715ccf67e358e5fc18fbfe6"
}]

View File

@ -0,0 +1,461 @@
[{
"testCaseDescription": "go-array-with-implicit-length-insert-test",
"expectedResult": {
"changes": {
"array-with-implicit-length.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
29
]
}
},
"summary": "Added the 'a1' variable"
}
]
},
"errors": {}
},
"filePaths": [
"array-with-implicit-length.go"
],
"patch": [
"diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
"index e69de29..96bef76 100644",
"--- a/array-with-implicit-length.go",
"+++ b/array-with-implicit-length.go",
"@@ -0,0 +1 @@",
"+const a1 = [...]int{1, 2, 3}"
],
"gitDir": "test/corpus/repos/go",
"shas": "0fff314fad0973ea89120a1ae3b7940e0f7866d2..d047fe40a9c741f62abe5a1313da6f36caca7979"
}
,{
"testCaseDescription": "go-array-with-implicit-length-replacement-insert-test",
"expectedResult": {
"changes": {
"array-with-implicit-length.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Added the 'a1' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
29
]
}
},
"summary": "Added the 'a1' variable"
}
]
},
"errors": {}
},
"filePaths": [
"array-with-implicit-length.go"
],
"patch": [
"diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
"index 96bef76..f49bee5 100644",
"--- a/array-with-implicit-length.go",
"+++ b/array-with-implicit-length.go",
"@@ -1 +1,3 @@",
"+const a1 = [...]int{4,5,6}",
"+const a1 = [...]int{1, 2, 3}",
" const a1 = [...]int{1, 2, 3}"
],
"gitDir": "test/corpus/repos/go",
"shas": "d047fe40a9c741f62abe5a1313da6f36caca7979..2fcb5b095ac3ea0981a515c3dd0f52c9212611d5"
}
,{
"testCaseDescription": "go-array-with-implicit-length-delete-insert-test",
"expectedResult": {
"changes": {
"array-with-implicit-length.go": [
{
"span": {
"replace": [
{
"start": [
1,
21
],
"end": [
1,
22
]
},
{
"start": [
1,
21
],
"end": [
1,
22
]
}
]
},
"summary": "Replaced '4' with '1' in the a1 variable"
},
{
"span": {
"insert": {
"start": [
1,
24
],
"end": [
1,
25
]
}
},
"summary": "Added '2' in the a1 variable"
},
{
"span": {
"replace": [
{
"start": [
1,
23
],
"end": [
1,
24
]
},
{
"start": [
1,
27
],
"end": [
1,
28
]
}
]
},
"summary": "Replaced '5' with '3' in the a1 variable"
},
{
"span": {
"delete": {
"start": [
1,
25
],
"end": [
1,
26
]
}
},
"summary": "Deleted '6' in the a1 variable"
}
]
},
"errors": {}
},
"filePaths": [
"array-with-implicit-length.go"
],
"patch": [
"diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
"index f49bee5..9dcd627 100644",
"--- a/array-with-implicit-length.go",
"+++ b/array-with-implicit-length.go",
"@@ -1,3 +1,3 @@",
"-const a1 = [...]int{4,5,6}",
"+const a1 = [...]int{1, 2, 3}",
" const a1 = [...]int{1, 2, 3}",
" const a1 = [...]int{1, 2, 3}"
],
"gitDir": "test/corpus/repos/go",
"shas": "2fcb5b095ac3ea0981a515c3dd0f52c9212611d5..f07306969d190ef934d9e77f78c1af6e6aeb0d63"
}
,{
"testCaseDescription": "go-array-with-implicit-length-replacement-test",
"expectedResult": {
"changes": {
"array-with-implicit-length.go": [
{
"span": {
"replace": [
{
"start": [
1,
21
],
"end": [
1,
22
]
},
{
"start": [
1,
21
],
"end": [
1,
22
]
}
]
},
"summary": "Replaced '1' with '4' in the a1 variable"
},
{
"span": {
"insert": {
"start": [
1,
23
],
"end": [
1,
24
]
}
},
"summary": "Added '5' in the a1 variable"
},
{
"span": {
"replace": [
{
"start": [
1,
24
],
"end": [
1,
25
]
},
{
"start": [
1,
25
],
"end": [
1,
26
]
}
]
},
"summary": "Replaced '2' with '6' in the a1 variable"
},
{
"span": {
"delete": {
"start": [
1,
27
],
"end": [
1,
28
]
}
},
"summary": "Deleted '3' in the a1 variable"
}
]
},
"errors": {}
},
"filePaths": [
"array-with-implicit-length.go"
],
"patch": [
"diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
"index 9dcd627..f49bee5 100644",
"--- a/array-with-implicit-length.go",
"+++ b/array-with-implicit-length.go",
"@@ -1,3 +1,3 @@",
"-const a1 = [...]int{1, 2, 3}",
"+const a1 = [...]int{4,5,6}",
" const a1 = [...]int{1, 2, 3}",
" const a1 = [...]int{1, 2, 3}"
],
"gitDir": "test/corpus/repos/go",
"shas": "f07306969d190ef934d9e77f78c1af6e6aeb0d63..c40f719c69cda9a21d80cdc1f985fd913875eb7e"
}
,{
"testCaseDescription": "go-array-with-implicit-length-delete-replacement-test",
"expectedResult": {
"changes": {
"array-with-implicit-length.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Deleted the 'a1' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
29
]
}
},
"summary": "Deleted the 'a1' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
27
]
}
},
"summary": "Added the 'a1' variable"
}
]
},
"errors": {}
},
"filePaths": [
"array-with-implicit-length.go"
],
"patch": [
"diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
"index f49bee5..47b9eed 100644",
"--- a/array-with-implicit-length.go",
"+++ b/array-with-implicit-length.go",
"@@ -1,3 +1,2 @@",
"-const a1 = [...]int{4,5,6}",
"-const a1 = [...]int{1, 2, 3}",
" const a1 = [...]int{1, 2, 3}",
"+const a1 = [...]int{4,5,6}"
],
"gitDir": "test/corpus/repos/go",
"shas": "c40f719c69cda9a21d80cdc1f985fd913875eb7e..6871f75087736569e032a112eaec06d72af2c580"
}
,{
"testCaseDescription": "go-array-with-implicit-length-delete-test",
"expectedResult": {
"changes": {
"array-with-implicit-length.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
29
]
}
},
"summary": "Deleted the 'a1' variable"
}
]
},
"errors": {}
},
"filePaths": [
"array-with-implicit-length.go"
],
"patch": [
"diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
"index 47b9eed..4a8295f 100644",
"--- a/array-with-implicit-length.go",
"+++ b/array-with-implicit-length.go",
"@@ -1,2 +1 @@",
"-const a1 = [...]int{1, 2, 3}",
" const a1 = [...]int{4,5,6}"
],
"gitDir": "test/corpus/repos/go",
"shas": "6871f75087736569e032a112eaec06d72af2c580..c4b7115fd6f988b0de691ac1ef1a25066093bfb3"
}
,{
"testCaseDescription": "go-array-with-implicit-length-delete-rest-test",
"expectedResult": {
"changes": {
"array-with-implicit-length.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Deleted the 'a1' variable"
}
]
},
"errors": {}
},
"filePaths": [
"array-with-implicit-length.go"
],
"patch": [
"diff --git a/array-with-implicit-length.go b/array-with-implicit-length.go",
"index 4a8295f..e69de29 100644",
"--- a/array-with-implicit-length.go",
"+++ b/array-with-implicit-length.go",
"@@ -1 +0,0 @@",
"-const a1 = [...]int{4,5,6}"
],
"gitDir": "test/corpus/repos/go",
"shas": "c4b7115fd6f988b0de691ac1ef1a25066093bfb3..f366494a187af73e7fcf6d60c2aa3bb503543f80"
}]

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,745 @@
[{
"testCaseDescription": "go-call-expressions-insert-test",
"expectedResult": {
"changes": {},
"errors": {
"call-expressions.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Added the 'x(b, c...)' at line 1, column 1 - line 1, column 11"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Added the 'y(b, c,)' at line 2, column 1 - line 2, column 9"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
11
]
}
},
"summary": "Added the 'z(b,c...,)' at line 3, column 1 - line 3, column 11"
}
]
}
},
"filePaths": [
"call-expressions.go"
],
"patch": [
"diff --git a/call-expressions.go b/call-expressions.go",
"index e69de29..ecd7132 100644",
"--- a/call-expressions.go",
"+++ b/call-expressions.go",
"@@ -0,0 +1,3 @@",
"+x(b, c...)",
"+y(b, c,)",
"+z(b,c...,)"
],
"gitDir": "test/corpus/repos/go",
"shas": "b47f159a4e69c481019748b1b4451ca5480b48ac..c8763d16606cda825fb974369f9a2b519439e29e"
}
,{
"testCaseDescription": "go-call-expressions-replacement-insert-test",
"expectedResult": {
"changes": {},
"errors": {
"call-expressions.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Added the 'a(b, c...)' at line 1, column 1 - line 1, column 11"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Added the 'b(b, c,)' at line 2, column 1 - line 2, column 9"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
11
]
}
},
"summary": "Added the 'c(b,c...,)' at line 3, column 1 - line 3, column 11"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
11
]
}
},
"summary": "Added the 'x(b, c...)' at line 4, column 1 - line 4, column 11"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
9
]
}
},
"summary": "Added the 'y(b, c,)' at line 5, column 1 - line 5, column 9"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
11
]
}
},
"summary": "Added the 'z(b,c...,)' at line 6, column 1 - line 6, column 11"
}
]
}
},
"filePaths": [
"call-expressions.go"
],
"patch": [
"diff --git a/call-expressions.go b/call-expressions.go",
"index ecd7132..d979c0a 100644",
"--- a/call-expressions.go",
"+++ b/call-expressions.go",
"@@ -1,3 +1,9 @@",
"+a(b, c...)",
"+b(b, c,)",
"+c(b,c...,)",
"+x(b, c...)",
"+y(b, c,)",
"+z(b,c...,)",
" x(b, c...)",
" y(b, c,)",
" z(b,c...,)"
],
"gitDir": "test/corpus/repos/go",
"shas": "c8763d16606cda825fb974369f9a2b519439e29e..efeb7a0f095a0f9412a310203ec9147cc43a093a"
}
,{
"testCaseDescription": "go-call-expressions-delete-insert-test",
"expectedResult": {
"changes": {},
"errors": {
"call-expressions.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Added the 'x(b, c...)' at line 1, column 1 - line 1, column 11"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Added the 'y(b, c,)' at line 2, column 1 - line 2, column 9"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
11
]
}
},
"summary": "Added the 'z(b,c...,)' at line 3, column 1 - line 3, column 11"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'a(b, c...)' at line 1, column 1 - line 1, column 11"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Deleted the 'b(b, c,)' at line 2, column 1 - line 2, column 9"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
11
]
}
},
"summary": "Deleted the 'c(b,c...,)' at line 3, column 1 - line 3, column 11"
}
]
}
},
"filePaths": [
"call-expressions.go"
],
"patch": [
"diff --git a/call-expressions.go b/call-expressions.go",
"index d979c0a..a3950ff 100644",
"--- a/call-expressions.go",
"+++ b/call-expressions.go",
"@@ -1,6 +1,6 @@",
"-a(b, c...)",
"-b(b, c,)",
"-c(b,c...,)",
"+x(b, c...)",
"+y(b, c,)",
"+z(b,c...,)",
" x(b, c...)",
" y(b, c,)",
" z(b,c...,)"
],
"gitDir": "test/corpus/repos/go",
"shas": "efeb7a0f095a0f9412a310203ec9147cc43a093a..9c07ff15f6bdc008d045bbaebae934200a2a6734"
}
,{
"testCaseDescription": "go-call-expressions-replacement-test",
"expectedResult": {
"changes": {},
"errors": {
"call-expressions.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Added the 'a(b, c...)' at line 1, column 1 - line 1, column 11"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Added the 'b(b, c,)' at line 2, column 1 - line 2, column 9"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
11
]
}
},
"summary": "Added the 'c(b,c...,)' at line 3, column 1 - line 3, column 11"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'x(b, c...)' at line 1, column 1 - line 1, column 11"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Deleted the 'y(b, c,)' at line 2, column 1 - line 2, column 9"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
11
]
}
},
"summary": "Deleted the 'z(b,c...,)' at line 3, column 1 - line 3, column 11"
}
]
}
},
"filePaths": [
"call-expressions.go"
],
"patch": [
"diff --git a/call-expressions.go b/call-expressions.go",
"index a3950ff..d979c0a 100644",
"--- a/call-expressions.go",
"+++ b/call-expressions.go",
"@@ -1,6 +1,6 @@",
"-x(b, c...)",
"-y(b, c,)",
"-z(b,c...,)",
"+a(b, c...)",
"+b(b, c,)",
"+c(b,c...,)",
" x(b, c...)",
" y(b, c,)",
" z(b,c...,)"
],
"gitDir": "test/corpus/repos/go",
"shas": "9c07ff15f6bdc008d045bbaebae934200a2a6734..a1710da50116f9380b25e096b698eec1b03325f6"
}
,{
"testCaseDescription": "go-call-expressions-delete-replacement-test",
"expectedResult": {
"changes": {},
"errors": {
"call-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'a(b, c...)' at line 1, column 1 - line 1, column 11"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Deleted the 'b(b, c,)' at line 2, column 1 - line 2, column 9"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
11
]
}
},
"summary": "Deleted the 'c(b,c...,)' at line 3, column 1 - line 3, column 11"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
11
]
}
},
"summary": "Deleted the 'x(b, c...)' at line 4, column 1 - line 4, column 11"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
5,
9
]
}
},
"summary": "Deleted the 'y(b, c,)' at line 5, column 1 - line 5, column 9"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
6,
11
]
}
},
"summary": "Deleted the 'z(b,c...,)' at line 6, column 1 - line 6, column 11"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
11
]
}
},
"summary": "Added the 'a(b, c...)' at line 4, column 1 - line 4, column 11"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
9
]
}
},
"summary": "Added the 'b(b, c,)' at line 5, column 1 - line 5, column 9"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
11
]
}
},
"summary": "Added the 'c(b,c...,)' at line 6, column 1 - line 6, column 11"
}
]
}
},
"filePaths": [
"call-expressions.go"
],
"patch": [
"diff --git a/call-expressions.go b/call-expressions.go",
"index d979c0a..589914d 100644",
"--- a/call-expressions.go",
"+++ b/call-expressions.go",
"@@ -1,9 +1,6 @@",
"-a(b, c...)",
"-b(b, c,)",
"-c(b,c...,)",
"-x(b, c...)",
"-y(b, c,)",
"-z(b,c...,)",
" x(b, c...)",
" y(b, c,)",
" z(b,c...,)",
"+a(b, c...)",
"+b(b, c,)",
"+c(b,c...,)"
],
"gitDir": "test/corpus/repos/go",
"shas": "a1710da50116f9380b25e096b698eec1b03325f6..a1c6a59603e72f43ab5a830e99818da54d6fb95b"
}
,{
"testCaseDescription": "go-call-expressions-delete-test",
"expectedResult": {
"changes": {},
"errors": {
"call-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'x(b, c...)' at line 1, column 1 - line 1, column 11"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Deleted the 'y(b, c,)' at line 2, column 1 - line 2, column 9"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
11
]
}
},
"summary": "Deleted the 'z(b,c...,)' at line 3, column 1 - line 3, column 11"
}
]
}
},
"filePaths": [
"call-expressions.go"
],
"patch": [
"diff --git a/call-expressions.go b/call-expressions.go",
"index 589914d..1dc566c 100644",
"--- a/call-expressions.go",
"+++ b/call-expressions.go",
"@@ -1,6 +1,3 @@",
"-x(b, c...)",
"-y(b, c,)",
"-z(b,c...,)",
" a(b, c...)",
" b(b, c,)",
" c(b,c...,)"
],
"gitDir": "test/corpus/repos/go",
"shas": "a1c6a59603e72f43ab5a830e99818da54d6fb95b..9293baf00488ad7785e23a8b78ab5f95342ebab3"
}
,{
"testCaseDescription": "go-call-expressions-delete-rest-test",
"expectedResult": {
"changes": {},
"errors": {
"call-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'a(b, c...)' at line 1, column 1 - line 1, column 11"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Deleted the 'b(b, c,)' at line 2, column 1 - line 2, column 9"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
11
]
}
},
"summary": "Deleted the 'c(b,c...,)' at line 3, column 1 - line 3, column 11"
}
]
}
},
"filePaths": [
"call-expressions.go"
],
"patch": [
"diff --git a/call-expressions.go b/call-expressions.go",
"index 1dc566c..e69de29 100644",
"--- a/call-expressions.go",
"+++ b/call-expressions.go",
"@@ -1,3 +0,0 @@",
"-a(b, c...)",
"-b(b, c,)",
"-c(b,c...,)"
],
"gitDir": "test/corpus/repos/go",
"shas": "9293baf00488ad7785e23a8b78ab5f95342ebab3..8cef11ced56e7aed74af10acde19377ccfe0b6af"
}]

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,491 @@
[{
"testCaseDescription": "go-const-declarations-with-types-insert-test",
"expectedResult": {
"changes": {
"const-declarations-with-types.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
19
]
}
},
"summary": "Added the 'zero' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-with-types.go"
],
"patch": [
"diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
"index e69de29..da3bfc4 100644",
"--- a/const-declarations-with-types.go",
"+++ b/const-declarations-with-types.go",
"@@ -0,0 +1 @@",
"+const zero int = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "32b315c37909ee768458a4eb9ea7845a06769621..961d92cdc9ebd9a80f0727b86581998c21fda958"
}
,{
"testCaseDescription": "go-const-declarations-with-types-replacement-insert-test",
"expectedResult": {
"changes": {
"const-declarations-with-types.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
30
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
30
]
}
},
"summary": "Added the 'two' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Added the 'zero' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-with-types.go"
],
"patch": [
"diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
"index da3bfc4..86f010e 100644",
"--- a/const-declarations-with-types.go",
"+++ b/const-declarations-with-types.go",
"@@ -1 +1,3 @@",
"+const one, two uiint64 = 1, 2",
"+const zero int = 0",
" const zero int = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "961d92cdc9ebd9a80f0727b86581998c21fda958..779569ab17705797005da9a929df5042304d6020"
}
,{
"testCaseDescription": "go-const-declarations-with-types-delete-insert-test",
"expectedResult": {
"changes": {
"const-declarations-with-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
7
],
"end": [
1,
10
]
},
{
"start": [
1,
7
],
"end": [
1,
11
]
}
]
},
"summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
1,
26
],
"end": [
1,
27
]
},
{
"start": [
1,
18
],
"end": [
1,
19
]
}
]
},
"summary": "Replaced '1' with '0' in the zero variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
30
]
}
},
"summary": "Deleted the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-with-types.go"
],
"patch": [
"diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
"index 86f010e..049ca7f 100644",
"--- a/const-declarations-with-types.go",
"+++ b/const-declarations-with-types.go",
"@@ -1,3 +1,3 @@",
"-const one, two uiint64 = 1, 2",
"+const zero int = 0",
" const zero int = 0",
" const zero int = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "779569ab17705797005da9a929df5042304d6020..f37b24c77b0054da8b553755c7729956dab62808"
}
,{
"testCaseDescription": "go-const-declarations-with-types-replacement-test",
"expectedResult": {
"changes": {
"const-declarations-with-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
7
],
"end": [
1,
11
]
},
{
"start": [
1,
7
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced the 'zero' identifier with the 'one' identifier in the one variable"
},
{
"span": {
"replace": [
{
"start": [
1,
18
],
"end": [
1,
19
]
},
{
"start": [
1,
26
],
"end": [
1,
27
]
}
]
},
"summary": "Replaced '0' with '1' in the one variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
30
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-with-types.go"
],
"patch": [
"diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
"index 049ca7f..86f010e 100644",
"--- a/const-declarations-with-types.go",
"+++ b/const-declarations-with-types.go",
"@@ -1,3 +1,3 @@",
"-const zero int = 0",
"+const one, two uiint64 = 1, 2",
" const zero int = 0",
" const zero int = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "f37b24c77b0054da8b553755c7729956dab62808..6294219449121c8cbd20d3ba524890dceb6e138e"
}
,{
"testCaseDescription": "go-const-declarations-with-types-delete-replacement-test",
"expectedResult": {
"changes": {
"const-declarations-with-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
30
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
30
]
}
},
"summary": "Deleted the 'two' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Deleted the 'zero' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
30
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
30
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-with-types.go"
],
"patch": [
"diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
"index 86f010e..f035105 100644",
"--- a/const-declarations-with-types.go",
"+++ b/const-declarations-with-types.go",
"@@ -1,3 +1,2 @@",
"-const one, two uiint64 = 1, 2",
"-const zero int = 0",
" const zero int = 0",
"+const one, two uiint64 = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "6294219449121c8cbd20d3ba524890dceb6e138e..7310b361570cf43ce24c55caf717fc64069a2d3b"
}
,{
"testCaseDescription": "go-const-declarations-with-types-delete-test",
"expectedResult": {
"changes": {
"const-declarations-with-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
19
]
}
},
"summary": "Deleted the 'zero' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-with-types.go"
],
"patch": [
"diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
"index f035105..716746a 100644",
"--- a/const-declarations-with-types.go",
"+++ b/const-declarations-with-types.go",
"@@ -1,2 +1 @@",
"-const zero int = 0",
" const one, two uiint64 = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "7310b361570cf43ce24c55caf717fc64069a2d3b..c3d27a164e9197991bd4390391a3699327e8e1b0"
}
,{
"testCaseDescription": "go-const-declarations-with-types-delete-rest-test",
"expectedResult": {
"changes": {
"const-declarations-with-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
30
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
30
]
}
},
"summary": "Deleted the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-with-types.go"
],
"patch": [
"diff --git a/const-declarations-with-types.go b/const-declarations-with-types.go",
"index 716746a..e69de29 100644",
"--- a/const-declarations-with-types.go",
"+++ b/const-declarations-with-types.go",
"@@ -1 +0,0 @@",
"-const one, two uiint64 = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "c3d27a164e9197991bd4390391a3699327e8e1b0..5352a466a13a8f3f02aa66c9a40c94ce75e0e613"
}]

View File

@ -0,0 +1,491 @@
[{
"testCaseDescription": "go-const-declarations-without-types-insert-test",
"expectedResult": {
"changes": {
"const-declarations-without-types.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
15
]
}
},
"summary": "Added the 'zero' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-without-types.go"
],
"patch": [
"diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
"index e69de29..2f2e175 100644",
"--- a/const-declarations-without-types.go",
"+++ b/const-declarations-without-types.go",
"@@ -0,0 +1 @@",
"+const zero = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "e3cc7c05800e63045739cf83cc9bed769e582946..7893139bc48344b1c6e4eb30e84badf05a6da6b9"
}
,{
"testCaseDescription": "go-const-declarations-without-types-replacement-insert-test",
"expectedResult": {
"changes": {
"const-declarations-without-types.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Added the 'two' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
15
]
}
},
"summary": "Added the 'zero' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-without-types.go"
],
"patch": [
"diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
"index 2f2e175..2d4a6fd 100644",
"--- a/const-declarations-without-types.go",
"+++ b/const-declarations-without-types.go",
"@@ -1 +1,3 @@",
"+const one, two = 1, 2",
"+const zero = 0",
" const zero = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "7893139bc48344b1c6e4eb30e84badf05a6da6b9..f2ca37e6df2f0e6601317ce53fa41dae85ac6eb7"
}
,{
"testCaseDescription": "go-const-declarations-without-types-delete-insert-test",
"expectedResult": {
"changes": {
"const-declarations-without-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
7
],
"end": [
1,
10
]
},
{
"start": [
1,
7
],
"end": [
1,
11
]
}
]
},
"summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
1,
18
],
"end": [
1,
19
]
},
{
"start": [
1,
14
],
"end": [
1,
15
]
}
]
},
"summary": "Replaced '1' with '0' in the zero variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Deleted the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-without-types.go"
],
"patch": [
"diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
"index 2d4a6fd..b60f29e 100644",
"--- a/const-declarations-without-types.go",
"+++ b/const-declarations-without-types.go",
"@@ -1,3 +1,3 @@",
"-const one, two = 1, 2",
"+const zero = 0",
" const zero = 0",
" const zero = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "f2ca37e6df2f0e6601317ce53fa41dae85ac6eb7..ac0f95fa20cf28c4db79a2d2a6ea3748cf3a5c53"
}
,{
"testCaseDescription": "go-const-declarations-without-types-replacement-test",
"expectedResult": {
"changes": {
"const-declarations-without-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
7
],
"end": [
1,
11
]
},
{
"start": [
1,
7
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced the 'zero' identifier with the 'one' identifier in the one variable"
},
{
"span": {
"replace": [
{
"start": [
1,
14
],
"end": [
1,
15
]
},
{
"start": [
1,
18
],
"end": [
1,
19
]
}
]
},
"summary": "Replaced '0' with '1' in the one variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-without-types.go"
],
"patch": [
"diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
"index b60f29e..2d4a6fd 100644",
"--- a/const-declarations-without-types.go",
"+++ b/const-declarations-without-types.go",
"@@ -1,3 +1,3 @@",
"-const zero = 0",
"+const one, two = 1, 2",
" const zero = 0",
" const zero = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "ac0f95fa20cf28c4db79a2d2a6ea3748cf3a5c53..cc922e34d63773be705f8bb45da94eb6633d6d9d"
}
,{
"testCaseDescription": "go-const-declarations-without-types-delete-replacement-test",
"expectedResult": {
"changes": {
"const-declarations-without-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Deleted the 'two' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
15
]
}
},
"summary": "Deleted the 'zero' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
22
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
22
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-without-types.go"
],
"patch": [
"diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
"index 2d4a6fd..0cb8229 100644",
"--- a/const-declarations-without-types.go",
"+++ b/const-declarations-without-types.go",
"@@ -1,3 +1,2 @@",
"-const one, two = 1, 2",
"-const zero = 0",
" const zero = 0",
"+const one, two = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "cc922e34d63773be705f8bb45da94eb6633d6d9d..4f7206f8d97e09d920a16ed0d34acd5d03a7993a"
}
,{
"testCaseDescription": "go-const-declarations-without-types-delete-test",
"expectedResult": {
"changes": {
"const-declarations-without-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
15
]
}
},
"summary": "Deleted the 'zero' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-without-types.go"
],
"patch": [
"diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
"index 0cb8229..83cc71f 100644",
"--- a/const-declarations-without-types.go",
"+++ b/const-declarations-without-types.go",
"@@ -1,2 +1 @@",
"-const zero = 0",
" const one, two = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "4f7206f8d97e09d920a16ed0d34acd5d03a7993a..65836ac955a739028b5745b140b306784a47fadf"
}
,{
"testCaseDescription": "go-const-declarations-without-types-delete-rest-test",
"expectedResult": {
"changes": {
"const-declarations-without-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Deleted the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-declarations-without-types.go"
],
"patch": [
"diff --git a/const-declarations-without-types.go b/const-declarations-without-types.go",
"index 83cc71f..e69de29 100644",
"--- a/const-declarations-without-types.go",
"+++ b/const-declarations-without-types.go",
"@@ -1 +0,0 @@",
"-const one, two = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "65836ac955a739028b5745b140b306784a47fadf..32b315c37909ee768458a4eb9ea7845a06769621"
}]

View File

@ -0,0 +1,747 @@
[{
"testCaseDescription": "go-const-with-implicit-values-insert-test",
"expectedResult": {
"changes": {
"const-with-implicit-values.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Added the 'zero' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-with-implicit-values.go"
],
"patch": [
"diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
"index e69de29..938a571 100644",
"--- a/const-with-implicit-values.go",
"+++ b/const-with-implicit-values.go",
"@@ -0,0 +1,5 @@",
"+const (",
"+ zero = iota",
"+ one",
"+ two",
"+ )"
],
"gitDir": "test/corpus/repos/go",
"shas": "eab68be4fe73c7ea63793058e38316a7eab75064..9c08f71afc4f67ed8399c2904fa3c511085e32fa"
}
,{
"testCaseDescription": "go-const-with-implicit-values-replacement-insert-test",
"expectedResult": {
"changes": {
"const-with-implicit-values.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Added the 'b' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Added the 'c' variable"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
3
]
}
},
"summary": "Added the 'zero' variable"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
3
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
3
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-with-implicit-values.go"
],
"patch": [
"diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
"index 938a571..071b359 100644",
"--- a/const-with-implicit-values.go",
"+++ b/const-with-implicit-values.go",
"@@ -1,4 +1,14 @@",
" const (",
"+ a = iota",
"+ b",
"+ c",
"+ )",
"+const (",
"+ zero = iota",
"+ one",
"+ two",
"+ )",
"+const (",
" zero = iota",
" one",
" two"
],
"gitDir": "test/corpus/repos/go",
"shas": "9c08f71afc4f67ed8399c2904fa3c511085e32fa..a3fffc055f14421a39ce87b49fc3ac583af306f1"
}
,{
"testCaseDescription": "go-const-with-implicit-values-delete-insert-test",
"expectedResult": {
"changes": {
"const-with-implicit-values.go": [
{
"span": {
"replace": [
{
"start": [
2,
2
],
"end": [
2,
3
]
},
{
"start": [
2,
2
],
"end": [
2,
6
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
3,
2
],
"end": [
3,
3
]
},
{
"start": [
3,
2
],
"end": [
3,
5
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'one' identifier"
},
{
"span": {
"replace": [
{
"start": [
4,
2
],
"end": [
4,
3
]
},
{
"start": [
4,
2
],
"end": [
4,
5
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'two' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"const-with-implicit-values.go"
],
"patch": [
"diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
"index 071b359..8a6d638 100644",
"--- a/const-with-implicit-values.go",
"+++ b/const-with-implicit-values.go",
"@@ -1,7 +1,7 @@",
" const (",
"- a = iota",
"- b",
"- c",
"+ zero = iota",
"+ one",
"+ two",
" )",
" const (",
" zero = iota"
],
"gitDir": "test/corpus/repos/go",
"shas": "a3fffc055f14421a39ce87b49fc3ac583af306f1..2c83dd0ff7ac9b61cd2d2155917f60c1578bd472"
}
,{
"testCaseDescription": "go-const-with-implicit-values-replacement-test",
"expectedResult": {
"changes": {
"const-with-implicit-values.go": [
{
"span": {
"replace": [
{
"start": [
2,
2
],
"end": [
2,
6
]
},
{
"start": [
2,
2
],
"end": [
2,
3
]
}
]
},
"summary": "Replaced the 'zero' identifier with the 'a' identifier in the a variable"
},
{
"span": {
"replace": [
{
"start": [
3,
2
],
"end": [
3,
5
]
},
{
"start": [
3,
2
],
"end": [
3,
3
]
}
]
},
"summary": "Replaced the 'one' identifier with the 'b' identifier"
},
{
"span": {
"replace": [
{
"start": [
4,
2
],
"end": [
4,
5
]
},
{
"start": [
4,
2
],
"end": [
4,
3
]
}
]
},
"summary": "Replaced the 'two' identifier with the 'c' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"const-with-implicit-values.go"
],
"patch": [
"diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
"index 8a6d638..071b359 100644",
"--- a/const-with-implicit-values.go",
"+++ b/const-with-implicit-values.go",
"@@ -1,7 +1,7 @@",
" const (",
"- zero = iota",
"- one",
"- two",
"+ a = iota",
"+ b",
"+ c",
" )",
" const (",
" zero = iota"
],
"gitDir": "test/corpus/repos/go",
"shas": "2c83dd0ff7ac9b61cd2d2155917f60c1578bd472..eaa7f3281ecec5fa706b862a28ae1cfbcdac382d"
}
,{
"testCaseDescription": "go-const-with-implicit-values-delete-replacement-test",
"expectedResult": {
"changes": {
"const-with-implicit-values.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Deleted the 'c' variable"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
10,
3
]
}
},
"summary": "Deleted the 'zero' variable"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
10,
3
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
10,
3
]
}
},
"summary": "Deleted the 'two' variable"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
3
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
3
]
}
},
"summary": "Added the 'b' variable"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
3
]
}
},
"summary": "Added the 'c' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-with-implicit-values.go"
],
"patch": [
"diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
"index 071b359..ae8b277 100644",
"--- a/const-with-implicit-values.go",
"+++ b/const-with-implicit-values.go",
"@@ -1,15 +1,10 @@",
" const (",
"- a = iota",
"- b",
"- c",
"- )",
"-const (",
" zero = iota",
" one",
" two",
" )",
" const (",
"- zero = iota",
"- one",
"- two",
"+ a = iota",
"+ b",
"+ c",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "eaa7f3281ecec5fa706b862a28ae1cfbcdac382d..697b694fcc19b4223284ab44c961bd9544dcdaa3"
}
,{
"testCaseDescription": "go-const-with-implicit-values-delete-test",
"expectedResult": {
"changes": {
"const-with-implicit-values.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Deleted the 'zero' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Deleted the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-with-implicit-values.go"
],
"patch": [
"diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
"index ae8b277..dfb4fad 100644",
"--- a/const-with-implicit-values.go",
"+++ b/const-with-implicit-values.go",
"@@ -1,9 +1,4 @@",
" const (",
"- zero = iota",
"- one",
"- two",
"- )",
"-const (",
" a = iota",
" b",
" c"
],
"gitDir": "test/corpus/repos/go",
"shas": "697b694fcc19b4223284ab44c961bd9544dcdaa3..512cbb151aefa21474c28b2baae09a6eee09bcf5"
}
,{
"testCaseDescription": "go-const-with-implicit-values-delete-rest-test",
"expectedResult": {
"changes": {
"const-with-implicit-values.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
3
]
}
},
"summary": "Deleted the 'c' variable"
}
]
},
"errors": {}
},
"filePaths": [
"const-with-implicit-values.go"
],
"patch": [
"diff --git a/const-with-implicit-values.go b/const-with-implicit-values.go",
"index dfb4fad..e69de29 100644",
"--- a/const-with-implicit-values.go",
"+++ b/const-with-implicit-values.go",
"@@ -1,5 +0,0 @@",
"-const (",
"- a = iota",
"- b",
"- c",
"- )"
],
"gitDir": "test/corpus/repos/go",
"shas": "512cbb151aefa21474c28b2baae09a6eee09bcf5..966bee07072f36b83494af4ac7d3c83673e1f3f8"
}]

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,929 @@
[{
"testCaseDescription": "go-function-declarations-insert-test",
"expectedResult": {
"changes": {
"function-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'f1' function"
}
]
},
"errors": {
"function-declarations.go": [
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
38
]
}
},
"summary": "Added the 'func f2(a int, b, c, d string) int {}' at line 2, column 1 - line 2, column 38"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
26
]
}
},
"summary": "Added the 'func f2() (int, error) {}' at line 3, column 1 - line 3, column 26"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
37
]
}
},
"summary": "Added the 'func f2() (result int, err error) {}' at line 4, column 1 - line 4, column 37"
}
]
}
},
"filePaths": [
"function-declarations.go"
],
"patch": [
"diff --git a/function-declarations.go b/function-declarations.go",
"index e69de29..21da2ea 100644",
"--- a/function-declarations.go",
"+++ b/function-declarations.go",
"@@ -0,0 +1,4 @@",
"+func f1() {}",
"+func f2(a int, b, c, d string) int {}",
"+func f2() (int, error) {}",
"+func f2() (result int, err error) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "1cfc4770f33afe51641b5c1ed9683984d1ac4ae5..b8ea4fd0800ac92d14585218798b6958a31c0fc7"
}
,{
"testCaseDescription": "go-function-declarations-replacement-insert-test",
"expectedResult": {
"changes": {
"function-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'fa' function"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
13
]
}
},
"summary": "Added the 'f1' function"
}
]
},
"errors": {
"function-declarations.go": [
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
38
]
}
},
"summary": "Added the 'func fb(a int, b, c, d string) int {}' at line 2, column 1 - line 2, column 38"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
26
]
}
},
"summary": "Added the 'func fc() (int, error) {}' at line 3, column 1 - line 3, column 26"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
37
]
}
},
"summary": "Added the 'func fd() (result int, err error) {}' at line 4, column 1 - line 4, column 37"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
38
]
}
},
"summary": "Added the 'func f2(a int, b, c, d string) int {}' at line 6, column 1 - line 6, column 38"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
7,
26
]
}
},
"summary": "Added the 'func f2() (int, error) {}' at line 7, column 1 - line 7, column 26"
},
{
"span": {
"insert": {
"start": [
8,
1
],
"end": [
8,
37
]
}
},
"summary": "Added the 'func f2() (result int, err error) {}' at line 8, column 1 - line 8, column 37"
}
]
}
},
"filePaths": [
"function-declarations.go"
],
"patch": [
"diff --git a/function-declarations.go b/function-declarations.go",
"index 21da2ea..768679a 100644",
"--- a/function-declarations.go",
"+++ b/function-declarations.go",
"@@ -1,3 +1,11 @@",
"+func fa() {}",
"+func fb(a int, b, c, d string) int {}",
"+func fc() (int, error) {}",
"+func fd() (result int, err error) {}",
"+func f1() {}",
"+func f2(a int, b, c, d string) int {}",
"+func f2() (int, error) {}",
"+func f2() (result int, err error) {}",
" func f1() {}",
" func f2(a int, b, c, d string) int {}",
" func f2() (int, error) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "b8ea4fd0800ac92d14585218798b6958a31c0fc7..fcf6ccf0f476627c8abc746a558adb081ed9d7fa"
}
,{
"testCaseDescription": "go-function-declarations-delete-insert-test",
"expectedResult": {
"changes": {
"function-declarations.go": [
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
8
]
},
{
"start": [
1,
6
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced the 'fa' identifier with the 'f1' identifier in the f1 function"
},
{
"span": {
"replace": [
{
"start": [
2,
6
],
"end": [
2,
8
]
},
{
"start": [
2,
6
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the 'fb' identifier with the 'f2' identifier"
},
{
"span": {
"replace": [
{
"start": [
3,
6
],
"end": [
3,
8
]
},
{
"start": [
3,
6
],
"end": [
3,
8
]
}
]
},
"summary": "Replaced the 'fc' identifier with the 'f2' identifier"
},
{
"span": {
"replace": [
{
"start": [
4,
6
],
"end": [
4,
8
]
},
{
"start": [
4,
6
],
"end": [
4,
8
]
}
]
},
"summary": "Replaced the 'fd' identifier with the 'f2' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"function-declarations.go"
],
"patch": [
"diff --git a/function-declarations.go b/function-declarations.go",
"index 768679a..da899b5 100644",
"--- a/function-declarations.go",
"+++ b/function-declarations.go",
"@@ -1,7 +1,7 @@",
"-func fa() {}",
"-func fb(a int, b, c, d string) int {}",
"-func fc() (int, error) {}",
"-func fd() (result int, err error) {}",
"+func f1() {}",
"+func f2(a int, b, c, d string) int {}",
"+func f2() (int, error) {}",
"+func f2() (result int, err error) {}",
" func f1() {}",
" func f2(a int, b, c, d string) int {}",
" func f2() (int, error) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "fcf6ccf0f476627c8abc746a558adb081ed9d7fa..94fb4817ecc9299b9e1dd90ac05f48c53f5f984a"
}
,{
"testCaseDescription": "go-function-declarations-replacement-test",
"expectedResult": {
"changes": {
"function-declarations.go": [
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
8
]
},
{
"start": [
1,
6
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced the 'f1' identifier with the 'fa' identifier in the fa function"
},
{
"span": {
"replace": [
{
"start": [
2,
6
],
"end": [
2,
8
]
},
{
"start": [
2,
6
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the 'f2' identifier with the 'fb' identifier"
},
{
"span": {
"replace": [
{
"start": [
3,
6
],
"end": [
3,
8
]
},
{
"start": [
3,
6
],
"end": [
3,
8
]
}
]
},
"summary": "Replaced the 'f2' identifier with the 'fc' identifier"
},
{
"span": {
"replace": [
{
"start": [
4,
6
],
"end": [
4,
8
]
},
{
"start": [
4,
6
],
"end": [
4,
8
]
}
]
},
"summary": "Replaced the 'f2' identifier with the 'fd' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"function-declarations.go"
],
"patch": [
"diff --git a/function-declarations.go b/function-declarations.go",
"index da899b5..768679a 100644",
"--- a/function-declarations.go",
"+++ b/function-declarations.go",
"@@ -1,7 +1,7 @@",
"-func f1() {}",
"-func f2(a int, b, c, d string) int {}",
"-func f2() (int, error) {}",
"-func f2() (result int, err error) {}",
"+func fa() {}",
"+func fb(a int, b, c, d string) int {}",
"+func fc() (int, error) {}",
"+func fd() (result int, err error) {}",
" func f1() {}",
" func f2(a int, b, c, d string) int {}",
" func f2() (int, error) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "94fb4817ecc9299b9e1dd90ac05f48c53f5f984a..b60b66e9fa94b50e4756d060078a0804547be3d9"
}
,{
"testCaseDescription": "go-function-declarations-delete-replacement-test",
"expectedResult": {
"changes": {
"function-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'fa' function"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
5,
13
]
}
},
"summary": "Deleted the 'f1' function"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
13
]
}
},
"summary": "Added the 'fa' function"
}
]
},
"errors": {
"function-declarations.go": [
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
38
]
}
},
"summary": "Deleted the 'func fb(a int, b, c, d string) int {}' at line 2, column 1 - line 2, column 38"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
26
]
}
},
"summary": "Deleted the 'func fc() (int, error) {}' at line 3, column 1 - line 3, column 26"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
37
]
}
},
"summary": "Deleted the 'func fd() (result int, err error) {}' at line 4, column 1 - line 4, column 37"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
6,
38
]
}
},
"summary": "Deleted the 'func f2(a int, b, c, d string) int {}' at line 6, column 1 - line 6, column 38"
},
{
"span": {
"delete": {
"start": [
7,
1
],
"end": [
7,
26
]
}
},
"summary": "Deleted the 'func f2() (int, error) {}' at line 7, column 1 - line 7, column 26"
},
{
"span": {
"delete": {
"start": [
8,
1
],
"end": [
8,
37
]
}
},
"summary": "Deleted the 'func f2() (result int, err error) {}' at line 8, column 1 - line 8, column 37"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
38
]
}
},
"summary": "Added the 'func fb(a int, b, c, d string) int {}' at line 6, column 1 - line 6, column 38"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
7,
26
]
}
},
"summary": "Added the 'func fc() (int, error) {}' at line 7, column 1 - line 7, column 26"
},
{
"span": {
"insert": {
"start": [
8,
1
],
"end": [
8,
37
]
}
},
"summary": "Added the 'func fd() (result int, err error) {}' at line 8, column 1 - line 8, column 37"
}
]
}
},
"filePaths": [
"function-declarations.go"
],
"patch": [
"diff --git a/function-declarations.go b/function-declarations.go",
"index 768679a..306f918 100644",
"--- a/function-declarations.go",
"+++ b/function-declarations.go",
"@@ -1,12 +1,8 @@",
"-func fa() {}",
"-func fb(a int, b, c, d string) int {}",
"-func fc() (int, error) {}",
"-func fd() (result int, err error) {}",
"-func f1() {}",
"-func f2(a int, b, c, d string) int {}",
"-func f2() (int, error) {}",
"-func f2() (result int, err error) {}",
" func f1() {}",
" func f2(a int, b, c, d string) int {}",
" func f2() (int, error) {}",
" func f2() (result int, err error) {}",
"+func fa() {}",
"+func fb(a int, b, c, d string) int {}",
"+func fc() (int, error) {}",
"+func fd() (result int, err error) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "b60b66e9fa94b50e4756d060078a0804547be3d9..9677cee90e50ac019d16f74a7499da0d81896c91"
}
,{
"testCaseDescription": "go-function-declarations-delete-test",
"expectedResult": {
"changes": {
"function-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'f1' function"
}
]
},
"errors": {
"function-declarations.go": [
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
38
]
}
},
"summary": "Deleted the 'func f2(a int, b, c, d string) int {}' at line 2, column 1 - line 2, column 38"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
26
]
}
},
"summary": "Deleted the 'func f2() (int, error) {}' at line 3, column 1 - line 3, column 26"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
37
]
}
},
"summary": "Deleted the 'func f2() (result int, err error) {}' at line 4, column 1 - line 4, column 37"
}
]
}
},
"filePaths": [
"function-declarations.go"
],
"patch": [
"diff --git a/function-declarations.go b/function-declarations.go",
"index 306f918..cc84bb3 100644",
"--- a/function-declarations.go",
"+++ b/function-declarations.go",
"@@ -1,7 +1,3 @@",
"-func f1() {}",
"-func f2(a int, b, c, d string) int {}",
"-func f2() (int, error) {}",
"-func f2() (result int, err error) {}",
" func fa() {}",
" func fb(a int, b, c, d string) int {}",
" func fc() (int, error) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "9677cee90e50ac019d16f74a7499da0d81896c91..3847a6a7099687b768bdfc04aad517f2df75bf47"
}
,{
"testCaseDescription": "go-function-declarations-delete-rest-test",
"expectedResult": {
"changes": {
"function-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'fa' function"
}
]
},
"errors": {
"function-declarations.go": [
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
38
]
}
},
"summary": "Deleted the 'func fb(a int, b, c, d string) int {}' at line 2, column 1 - line 2, column 38"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
26
]
}
},
"summary": "Deleted the 'func fc() (int, error) {}' at line 3, column 1 - line 3, column 26"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
37
]
}
},
"summary": "Deleted the 'func fd() (result int, err error) {}' at line 4, column 1 - line 4, column 37"
}
]
}
},
"filePaths": [
"function-declarations.go"
],
"patch": [
"diff --git a/function-declarations.go b/function-declarations.go",
"index cc84bb3..e69de29 100644",
"--- a/function-declarations.go",
"+++ b/function-declarations.go",
"@@ -1,4 +0,0 @@",
"-func fa() {}",
"-func fb(a int, b, c, d string) int {}",
"-func fc() (int, error) {}",
"-func fd() (result int, err error) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "3847a6a7099687b768bdfc04aad517f2df75bf47..03191e600093d2810fbd1457b8ce453f3a9696bf"
}]

View File

@ -0,0 +1,423 @@
[{
"testCaseDescription": "go-function-literals-insert-test",
"expectedResult": {
"changes": {
"function-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
3,
2
]
}
},
"summary": "Added the 's1' variable"
}
]
},
"errors": {}
},
"filePaths": [
"function-literals.go"
],
"patch": [
"diff --git a/function-literals.go b/function-literals.go",
"index e69de29..49cbe77 100644",
"--- a/function-literals.go",
"+++ b/function-literals.go",
"@@ -0,0 +1,3 @@",
"+const s1 = func(s string) (int, int) {",
"+return 1, 2",
"+}"
],
"gitDir": "test/corpus/repos/go",
"shas": "8cef11ced56e7aed74af10acde19377ccfe0b6af..1dc216376d4051127f8fc7833470538864904865"
}
,{
"testCaseDescription": "go-function-literals-replacement-insert-test",
"expectedResult": {
"changes": {
"function-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
3,
2
]
}
},
"summary": "Added the 's1' variable"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
6,
2
]
}
},
"summary": "Added the 's1' variable"
}
]
},
"errors": {}
},
"filePaths": [
"function-literals.go"
],
"patch": [
"diff --git a/function-literals.go b/function-literals.go",
"index 49cbe77..913c35a 100644",
"--- a/function-literals.go",
"+++ b/function-literals.go",
"@@ -1,3 +1,9 @@",
"+const s1 = func(b int) (string, string) {",
"+return 1, 2",
"+}",
"+const s1 = func(s string) (int, int) {",
"+return 1, 2",
"+}",
" const s1 = func(s string) (int, int) {",
" return 1, 2",
" }"
],
"gitDir": "test/corpus/repos/go",
"shas": "1dc216376d4051127f8fc7833470538864904865..0a1fc24e689a77c0b136e4702b5328ccfac82601"
}
,{
"testCaseDescription": "go-function-literals-delete-insert-test",
"expectedResult": {
"changes": {
"function-literals.go": [
{
"span": {
"replace": [
{
"start": [
1,
17
],
"end": [
1,
18
]
},
{
"start": [
1,
17
],
"end": [
1,
18
]
}
]
},
"summary": "Replaced the 'b' identifier with the 's' identifier in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
1,
19
],
"end": [
1,
22
]
},
{
"start": [
1,
19
],
"end": [
1,
25
]
}
]
},
"summary": "Replaced the 'int' identifier with the 'string' identifier in the s1 variable"
}
]
},
"errors": {}
},
"filePaths": [
"function-literals.go"
],
"patch": [
"diff --git a/function-literals.go b/function-literals.go",
"index 913c35a..731e2c6 100644",
"--- a/function-literals.go",
"+++ b/function-literals.go",
"@@ -1,4 +1,4 @@",
"-const s1 = func(b int) (string, string) {",
"+const s1 = func(s string) (int, int) {",
" return 1, 2",
" }",
" const s1 = func(s string) (int, int) {"
],
"gitDir": "test/corpus/repos/go",
"shas": "0a1fc24e689a77c0b136e4702b5328ccfac82601..a91d7138a089662fc0100619eaeff8fd15c4fbed"
}
,{
"testCaseDescription": "go-function-literals-replacement-test",
"expectedResult": {
"changes": {
"function-literals.go": [
{
"span": {
"replace": [
{
"start": [
1,
17
],
"end": [
1,
18
]
},
{
"start": [
1,
17
],
"end": [
1,
18
]
}
]
},
"summary": "Replaced the 's' identifier with the 'b' identifier in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
1,
19
],
"end": [
1,
25
]
},
{
"start": [
1,
19
],
"end": [
1,
22
]
}
]
},
"summary": "Replaced the 'string' identifier with the 'int' identifier in the s1 variable"
}
]
},
"errors": {}
},
"filePaths": [
"function-literals.go"
],
"patch": [
"diff --git a/function-literals.go b/function-literals.go",
"index 731e2c6..913c35a 100644",
"--- a/function-literals.go",
"+++ b/function-literals.go",
"@@ -1,4 +1,4 @@",
"-const s1 = func(s string) (int, int) {",
"+const s1 = func(b int) (string, string) {",
" return 1, 2",
" }",
" const s1 = func(s string) (int, int) {"
],
"gitDir": "test/corpus/repos/go",
"shas": "a91d7138a089662fc0100619eaeff8fd15c4fbed..ad88b2ad21c0631a650d20f3b876ef0db92ec589"
}
,{
"testCaseDescription": "go-function-literals-delete-replacement-test",
"expectedResult": {
"changes": {
"function-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
3,
2
]
}
},
"summary": "Deleted the 's1' variable"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
6,
2
]
}
},
"summary": "Deleted the 's1' variable"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
6,
2
]
}
},
"summary": "Added the 's1' variable"
}
]
},
"errors": {}
},
"filePaths": [
"function-literals.go"
],
"patch": [
"diff --git a/function-literals.go b/function-literals.go",
"index 913c35a..51820bc 100644",
"--- a/function-literals.go",
"+++ b/function-literals.go",
"@@ -1,9 +1,6 @@",
"-const s1 = func(b int) (string, string) {",
"-return 1, 2",
"-}",
" const s1 = func(s string) (int, int) {",
" return 1, 2",
" }",
"-const s1 = func(s string) (int, int) {",
"+const s1 = func(b int) (string, string) {",
" return 1, 2",
" }"
],
"gitDir": "test/corpus/repos/go",
"shas": "ad88b2ad21c0631a650d20f3b876ef0db92ec589..54387de238ddc7806f785f4b874a5fcf20c70808"
}
,{
"testCaseDescription": "go-function-literals-delete-test",
"expectedResult": {
"changes": {
"function-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
3,
2
]
}
},
"summary": "Deleted the 's1' variable"
}
]
},
"errors": {}
},
"filePaths": [
"function-literals.go"
],
"patch": [
"diff --git a/function-literals.go b/function-literals.go",
"index 51820bc..d21dc2d 100644",
"--- a/function-literals.go",
"+++ b/function-literals.go",
"@@ -1,6 +1,3 @@",
"-const s1 = func(s string) (int, int) {",
"-return 1, 2",
"-}",
" const s1 = func(b int) (string, string) {",
" return 1, 2",
" }"
],
"gitDir": "test/corpus/repos/go",
"shas": "54387de238ddc7806f785f4b874a5fcf20c70808..68548df887acedb0540ef6087756db5c6a0a5c47"
}
,{
"testCaseDescription": "go-function-literals-delete-rest-test",
"expectedResult": {
"changes": {
"function-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
3,
2
]
}
},
"summary": "Deleted the 's1' variable"
}
]
},
"errors": {}
},
"filePaths": [
"function-literals.go"
],
"patch": [
"diff --git a/function-literals.go b/function-literals.go",
"index d21dc2d..e69de29 100644",
"--- a/function-literals.go",
"+++ b/function-literals.go",
"@@ -1,3 +0,0 @@",
"-const s1 = func(b int) (string, string) {",
"-return 1, 2",
"-}"
],
"gitDir": "test/corpus/repos/go",
"shas": "68548df887acedb0540ef6087756db5c6a0a5c47..e3cc7c05800e63045739cf83cc9bed769e582946"
}]

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,646 @@
[{
"testCaseDescription": "go-go-and-defer-statements-insert-test",
"expectedResult": {
"changes": {
"go-and-defer-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
12
]
}
},
"summary": "Added the 'x[y]()' defer statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Added the 'x[y]()' go statement"
}
]
},
"errors": {}
},
"filePaths": [
"go-and-defer-statements.go"
],
"patch": [
"diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
"index e69de29..2638f27 100644",
"--- a/go-and-defer-statements.go",
"+++ b/go-and-defer-statements.go",
"@@ -0,0 +1,2 @@",
"+defer x.y()",
"+go x.y()"
],
"gitDir": "test/corpus/repos/go",
"shas": "201c2f06d17d14e12c9861e2a94372fc41441178..4c2c5d9bf86b0e00910db4151d8cb1be6e261245"
}
,{
"testCaseDescription": "go-go-and-defer-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"go-and-defer-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
12
]
}
},
"summary": "Added the 'a[b]()' defer statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Added the 'c[d]()' go statement"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
12
]
}
},
"summary": "Added the 'x[y]()' defer statement"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
9
]
}
},
"summary": "Added the 'x[y]()' go statement"
}
]
},
"errors": {}
},
"filePaths": [
"go-and-defer-statements.go"
],
"patch": [
"diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
"index 2638f27..0cb11d5 100644",
"--- a/go-and-defer-statements.go",
"+++ b/go-and-defer-statements.go",
"@@ -1,2 +1,6 @@",
"+defer a.b()",
"+go c.d()",
"+defer x.y()",
"+go x.y()",
" defer x.y()",
" go x.y()"
],
"gitDir": "test/corpus/repos/go",
"shas": "4c2c5d9bf86b0e00910db4151d8cb1be6e261245..0af27bad18af4c3f10e18adf6824bc24be7cdf18"
}
,{
"testCaseDescription": "go-go-and-defer-statements-delete-insert-test",
"expectedResult": {
"changes": {
"go-and-defer-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
7
],
"end": [
1,
8
]
},
{
"start": [
1,
7
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'x' identifier in the x[y] subscript access"
},
{
"span": {
"replace": [
{
"start": [
1,
9
],
"end": [
1,
10
]
},
{
"start": [
1,
9
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'y' identifier in the x[y] subscript access"
},
{
"span": {
"replace": [
{
"start": [
2,
4
],
"end": [
2,
5
]
},
{
"start": [
2,
4
],
"end": [
2,
5
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'x' identifier in the x[y] subscript access"
},
{
"span": {
"replace": [
{
"start": [
2,
6
],
"end": [
2,
7
]
},
{
"start": [
2,
6
],
"end": [
2,
7
]
}
]
},
"summary": "Replaced the 'd' identifier with the 'y' identifier in the x[y] subscript access"
}
]
},
"errors": {}
},
"filePaths": [
"go-and-defer-statements.go"
],
"patch": [
"diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
"index 0cb11d5..bdc42aa 100644",
"--- a/go-and-defer-statements.go",
"+++ b/go-and-defer-statements.go",
"@@ -1,5 +1,5 @@",
"-defer a.b()",
"-go c.d()",
"+defer x.y()",
"+go x.y()",
" defer x.y()",
" go x.y()",
" defer x.y()"
],
"gitDir": "test/corpus/repos/go",
"shas": "0af27bad18af4c3f10e18adf6824bc24be7cdf18..e8853de747eee3ecdd93e3344be1e54dbc28e8fe"
}
,{
"testCaseDescription": "go-go-and-defer-statements-replacement-test",
"expectedResult": {
"changes": {
"go-and-defer-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
7
],
"end": [
1,
8
]
},
{
"start": [
1,
7
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'a' identifier in the a[b] subscript access"
},
{
"span": {
"replace": [
{
"start": [
1,
9
],
"end": [
1,
10
]
},
{
"start": [
1,
9
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced the 'y' identifier with the 'b' identifier in the a[b] subscript access"
},
{
"span": {
"replace": [
{
"start": [
2,
4
],
"end": [
2,
5
]
},
{
"start": [
2,
4
],
"end": [
2,
5
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'c' identifier in the c[d] subscript access"
},
{
"span": {
"replace": [
{
"start": [
2,
6
],
"end": [
2,
7
]
},
{
"start": [
2,
6
],
"end": [
2,
7
]
}
]
},
"summary": "Replaced the 'y' identifier with the 'd' identifier in the c[d] subscript access"
}
]
},
"errors": {}
},
"filePaths": [
"go-and-defer-statements.go"
],
"patch": [
"diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
"index bdc42aa..0cb11d5 100644",
"--- a/go-and-defer-statements.go",
"+++ b/go-and-defer-statements.go",
"@@ -1,5 +1,5 @@",
"-defer x.y()",
"-go x.y()",
"+defer a.b()",
"+go c.d()",
" defer x.y()",
" go x.y()",
" defer x.y()"
],
"gitDir": "test/corpus/repos/go",
"shas": "e8853de747eee3ecdd93e3344be1e54dbc28e8fe..baf0c568b56a2909465365b10b1764e574ffdcbf"
}
,{
"testCaseDescription": "go-go-and-defer-statements-delete-replacement-test",
"expectedResult": {
"changes": {
"go-and-defer-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
12
]
}
},
"summary": "Deleted the 'a[b]()' defer statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Deleted the 'c[d]()' go statement"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
12
]
}
},
"summary": "Deleted the 'x[y]()' defer statement"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
9
]
}
},
"summary": "Deleted the 'x[y]()' go statement"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
12
]
}
},
"summary": "Added the 'a[b]()' defer statement"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
9
]
}
},
"summary": "Added the 'c[d]()' go statement"
}
]
},
"errors": {}
},
"filePaths": [
"go-and-defer-statements.go"
],
"patch": [
"diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
"index 0cb11d5..f18666e 100644",
"--- a/go-and-defer-statements.go",
"+++ b/go-and-defer-statements.go",
"@@ -1,6 +1,4 @@",
"-defer a.b()",
"-go c.d()",
"-defer x.y()",
"-go x.y()",
" defer x.y()",
" go x.y()",
"+defer a.b()",
"+go c.d()"
],
"gitDir": "test/corpus/repos/go",
"shas": "baf0c568b56a2909465365b10b1764e574ffdcbf..8449fd5df5a995e61d8ca8b450f83468e79a5246"
}
,{
"testCaseDescription": "go-go-and-defer-statements-delete-test",
"expectedResult": {
"changes": {
"go-and-defer-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
12
]
}
},
"summary": "Deleted the 'x[y]()' defer statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Deleted the 'x[y]()' go statement"
}
]
},
"errors": {}
},
"filePaths": [
"go-and-defer-statements.go"
],
"patch": [
"diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
"index f18666e..eefd2e4 100644",
"--- a/go-and-defer-statements.go",
"+++ b/go-and-defer-statements.go",
"@@ -1,4 +1,2 @@",
"-defer x.y()",
"-go x.y()",
" defer a.b()",
" go c.d()"
],
"gitDir": "test/corpus/repos/go",
"shas": "8449fd5df5a995e61d8ca8b450f83468e79a5246..129278c1c54e5bcd112a0f7bc5a4876b0890b5a9"
}
,{
"testCaseDescription": "go-go-and-defer-statements-delete-rest-test",
"expectedResult": {
"changes": {
"go-and-defer-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
12
]
}
},
"summary": "Deleted the 'a[b]()' defer statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Deleted the 'c[d]()' go statement"
}
]
},
"errors": {}
},
"filePaths": [
"go-and-defer-statements.go"
],
"patch": [
"diff --git a/go-and-defer-statements.go b/go-and-defer-statements.go",
"index eefd2e4..e69de29 100644",
"--- a/go-and-defer-statements.go",
"+++ b/go-and-defer-statements.go",
"@@ -1,2 +0,0 @@",
"-defer a.b()",
"-go c.d()"
],
"gitDir": "test/corpus/repos/go",
"shas": "129278c1c54e5bcd112a0f7bc5a4876b0890b5a9..13fa148e00739eba43f10562e024e15d2fc7e5d9"
}]

View File

@ -0,0 +1,762 @@
[{
"testCaseDescription": "go-grouped-import-declarations-insert-test",
"expectedResult": {
"changes": {
"grouped-import-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Added the \"net/http\" import statement"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Added the \"some/dsl\" import statement"
}
]
},
"errors": {
"grouped-import-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Added the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 1, column 1 - line 5, column 2"
}
]
}
},
"filePaths": [
"grouped-import-declarations.go"
],
"patch": [
"diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
"index e69de29..6560136 100644",
"--- a/grouped-import-declarations.go",
"+++ b/grouped-import-declarations.go",
"@@ -0,0 +1,5 @@",
"+import (",
"+\"net/http\"",
"+ . \"some/dsl\"",
"+ alias \"some/package\"",
"+)"
],
"gitDir": "test/corpus/repos/go",
"shas": "3a1a004fc80ca40433336cc35ed31bd631b4d589..233d90c5a8f2097b27795d5e5e5eecc5c3415a31"
}
,{
"testCaseDescription": "go-grouped-import-declarations-replacement-insert-test",
"expectedResult": {
"changes": {
"grouped-import-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Added the \"net/socket\" import statement"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Added the \"types/dsl\" import statement"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
2
]
}
},
"summary": "Added the \"net/http\" import statement"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
2
]
}
},
"summary": "Added the \"some/dsl\" import statement"
}
]
},
"errors": {
"grouped-import-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Added the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 1, column 1 - line 5, column 2"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
2
]
}
},
"summary": "Added the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 6, column 1 - line 10, column 2"
}
]
}
},
"filePaths": [
"grouped-import-declarations.go"
],
"patch": [
"diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
"index 6560136..31d6bd7 100644",
"--- a/grouped-import-declarations.go",
"+++ b/grouped-import-declarations.go",
"@@ -1,4 +1,14 @@",
" import (",
"+\"net/socket\"",
"+ . \"types/dsl\"",
"+ alias \"awesome/package\"",
"+)",
"+import (",
"+\"net/http\"",
"+ . \"some/dsl\"",
"+ alias \"some/package\"",
"+)",
"+import (",
" \"net/http\"",
" . \"some/dsl\"",
" alias \"some/package\""
],
"gitDir": "test/corpus/repos/go",
"shas": "233d90c5a8f2097b27795d5e5e5eecc5c3415a31..78e66d25bd964ed3c89453c89f7aaae054c874f0"
}
,{
"testCaseDescription": "go-grouped-import-declarations-delete-insert-test",
"expectedResult": {
"changes": {
"grouped-import-declarations.go": [
{
"span": {
"replace": [
{
"start": [
2,
1
],
"end": [
2,
13
]
},
{
"start": [
2,
1
],
"end": [
2,
11
]
}
]
},
"summary": "Replaced the \"net/socket\" string with the \"net/http\" string in the \"net/http\" import statement"
},
{
"span": {
"replace": [
{
"start": [
3,
5
],
"end": [
3,
16
]
},
{
"start": [
3,
5
],
"end": [
3,
15
]
}
]
},
"summary": "Replaced the \"types/dsl\" string with the \"some/dsl\" string in the \"some/dsl\" import statement"
},
{
"span": {
"replace": [
{
"start": [
4,
9
],
"end": [
4,
26
]
},
{
"start": [
4,
9
],
"end": [
4,
23
]
}
]
},
"summary": "Replaced the \"awesome/package\" string with the \"some/package\" string"
}
]
},
"errors": {}
},
"filePaths": [
"grouped-import-declarations.go"
],
"patch": [
"diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
"index 31d6bd7..b045ab3 100644",
"--- a/grouped-import-declarations.go",
"+++ b/grouped-import-declarations.go",
"@@ -1,7 +1,7 @@",
" import (",
"-\"net/socket\"",
"- . \"types/dsl\"",
"- alias \"awesome/package\"",
"+\"net/http\"",
"+ . \"some/dsl\"",
"+ alias \"some/package\"",
" )",
" import (",
" \"net/http\""
],
"gitDir": "test/corpus/repos/go",
"shas": "78e66d25bd964ed3c89453c89f7aaae054c874f0..e37ef96d6ab2271602eb954f430703de6c409c55"
}
,{
"testCaseDescription": "go-grouped-import-declarations-replacement-test",
"expectedResult": {
"changes": {
"grouped-import-declarations.go": [
{
"span": {
"replace": [
{
"start": [
2,
1
],
"end": [
2,
11
]
},
{
"start": [
2,
1
],
"end": [
2,
13
]
}
]
},
"summary": "Replaced the \"net/http\" string with the \"net/socket\" string in the \"net/socket\" import statement"
},
{
"span": {
"replace": [
{
"start": [
3,
5
],
"end": [
3,
15
]
},
{
"start": [
3,
5
],
"end": [
3,
16
]
}
]
},
"summary": "Replaced the \"some/dsl\" string with the \"types/dsl\" string in the \"types/dsl\" import statement"
},
{
"span": {
"replace": [
{
"start": [
4,
9
],
"end": [
4,
23
]
},
{
"start": [
4,
9
],
"end": [
4,
26
]
}
]
},
"summary": "Replaced the \"some/package\" string with the \"awesome/package\" string"
}
]
},
"errors": {}
},
"filePaths": [
"grouped-import-declarations.go"
],
"patch": [
"diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
"index b045ab3..31d6bd7 100644",
"--- a/grouped-import-declarations.go",
"+++ b/grouped-import-declarations.go",
"@@ -1,7 +1,7 @@",
" import (",
"-\"net/http\"",
"- . \"some/dsl\"",
"- alias \"some/package\"",
"+\"net/socket\"",
"+ . \"types/dsl\"",
"+ alias \"awesome/package\"",
" )",
" import (",
" \"net/http\""
],
"gitDir": "test/corpus/repos/go",
"shas": "e37ef96d6ab2271602eb954f430703de6c409c55..90f9553085893a3d87bd9797f65d3083643431c4"
}
,{
"testCaseDescription": "go-grouped-import-declarations-delete-replacement-test",
"expectedResult": {
"changes": {
"grouped-import-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Deleted the \"net/socket\" import statement"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Deleted the \"types/dsl\" import statement"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
10,
2
]
}
},
"summary": "Deleted the \"net/http\" import statement"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
10,
2
]
}
},
"summary": "Deleted the \"some/dsl\" import statement"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
2
]
}
},
"summary": "Added the \"net/socket\" import statement"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
2
]
}
},
"summary": "Added the \"types/dsl\" import statement"
}
]
},
"errors": {
"grouped-import-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Deleted the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 1, column 1 - line 5, column 2"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
10,
2
]
}
},
"summary": "Deleted the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 6, column 1 - line 10, column 2"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
10,
2
]
}
},
"summary": "Added the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 6, column 1 - line 10, column 2"
}
]
}
},
"filePaths": [
"grouped-import-declarations.go"
],
"patch": [
"diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
"index 31d6bd7..62facc6 100644",
"--- a/grouped-import-declarations.go",
"+++ b/grouped-import-declarations.go",
"@@ -1,15 +1,10 @@",
" import (",
"-\"net/socket\"",
"- . \"types/dsl\"",
"- alias \"awesome/package\"",
"-)",
"-import (",
" \"net/http\"",
" . \"some/dsl\"",
" alias \"some/package\"",
" )",
" import (",
"-\"net/http\"",
"- . \"some/dsl\"",
"- alias \"some/package\"",
"+\"net/socket\"",
"+ . \"types/dsl\"",
"+ alias \"awesome/package\"",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "90f9553085893a3d87bd9797f65d3083643431c4..5ea9646b5663b469d1d05d122fc573b0bbf249b6"
}
,{
"testCaseDescription": "go-grouped-import-declarations-delete-test",
"expectedResult": {
"changes": {
"grouped-import-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Deleted the \"net/http\" import statement"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Deleted the \"some/dsl\" import statement"
}
]
},
"errors": {
"grouped-import-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Deleted the 'import (\n\"net/http\"\n . \"some/dsl\"\n alias \"some/package\"\n)' at line 1, column 1 - line 5, column 2"
}
]
}
},
"filePaths": [
"grouped-import-declarations.go"
],
"patch": [
"diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
"index 62facc6..e2f9293 100644",
"--- a/grouped-import-declarations.go",
"+++ b/grouped-import-declarations.go",
"@@ -1,9 +1,4 @@",
" import (",
"-\"net/http\"",
"- . \"some/dsl\"",
"- alias \"some/package\"",
"-)",
"-import (",
" \"net/socket\"",
" . \"types/dsl\"",
" alias \"awesome/package\""
],
"gitDir": "test/corpus/repos/go",
"shas": "5ea9646b5663b469d1d05d122fc573b0bbf249b6..03ae54522feab408ae78aabc67aa66fb1bbd9e5d"
}
,{
"testCaseDescription": "go-grouped-import-declarations-delete-rest-test",
"expectedResult": {
"changes": {
"grouped-import-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Deleted the \"net/socket\" import statement"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Deleted the \"types/dsl\" import statement"
}
]
},
"errors": {
"grouped-import-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
5,
2
]
}
},
"summary": "Deleted the 'import (\n\"net/socket\"\n . \"types/dsl\"\n alias \"awesome/package\"\n)' at line 1, column 1 - line 5, column 2"
}
]
}
},
"filePaths": [
"grouped-import-declarations.go"
],
"patch": [
"diff --git a/grouped-import-declarations.go b/grouped-import-declarations.go",
"index e2f9293..e69de29 100644",
"--- a/grouped-import-declarations.go",
"+++ b/grouped-import-declarations.go",
"@@ -1,5 +0,0 @@",
"-import (",
"-\"net/socket\"",
"- . \"types/dsl\"",
"- alias \"awesome/package\"",
"-)"
],
"gitDir": "test/corpus/repos/go",
"shas": "03ae54522feab408ae78aabc67aa66fb1bbd9e5d..f506441da93c9b84b48df54338a1c9a9314a3f6b"
}]

View File

@ -0,0 +1,560 @@
[{
"testCaseDescription": "go-grouped-var-declarations-insert-test",
"expectedResult": {
"changes": {
"grouped-var-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'zero' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'one' variable"
}
]
},
"errors": {}
},
"filePaths": [
"grouped-var-declarations.go"
],
"patch": [
"diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
"index e69de29..c1c0b16 100644",
"--- a/grouped-var-declarations.go",
"+++ b/grouped-var-declarations.go",
"@@ -0,0 +1,4 @@",
"+var (",
"+zero = 0",
"+one = 1",
"+)"
],
"gitDir": "test/corpus/repos/go",
"shas": "87119afd9d847041735cf640ecc066ad2804a85f..3d2221718774634aaf05f9751f1eac96639c8867"
}
,{
"testCaseDescription": "go-grouped-var-declarations-replacement-insert-test",
"expectedResult": {
"changes": {
"grouped-var-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'b' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'zero' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'one' variable"
}
]
},
"errors": {}
},
"filePaths": [
"grouped-var-declarations.go"
],
"patch": [
"diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
"index c1c0b16..6b9c91d 100644",
"--- a/grouped-var-declarations.go",
"+++ b/grouped-var-declarations.go",
"@@ -1,4 +1,12 @@",
" var (",
"+a = 0",
"+b = 1",
"+)",
"+var (",
"+zero = 0",
"+one = 1",
"+)",
"+var (",
" zero = 0",
" one = 1",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "3d2221718774634aaf05f9751f1eac96639c8867..028abd80df67d44f7cd18c889e31248c955453ae"
}
,{
"testCaseDescription": "go-grouped-var-declarations-delete-insert-test",
"expectedResult": {
"changes": {
"grouped-var-declarations.go": [
{
"span": {
"replace": [
{
"start": [
2,
1
],
"end": [
2,
2
]
},
{
"start": [
2,
1
],
"end": [
2,
5
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
3,
1
],
"end": [
3,
2
]
},
{
"start": [
3,
1
],
"end": [
3,
4
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'one' identifier in the one variable"
}
]
},
"errors": {}
},
"filePaths": [
"grouped-var-declarations.go"
],
"patch": [
"diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
"index 6b9c91d..5ed0e06 100644",
"--- a/grouped-var-declarations.go",
"+++ b/grouped-var-declarations.go",
"@@ -1,6 +1,6 @@",
" var (",
"-a = 0",
"-b = 1",
"+zero = 0",
"+one = 1",
" )",
" var (",
" zero = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "028abd80df67d44f7cd18c889e31248c955453ae..25b8fae28eebfaaa5e88a04d68b10205a277ed91"
}
,{
"testCaseDescription": "go-grouped-var-declarations-replacement-test",
"expectedResult": {
"changes": {
"grouped-var-declarations.go": [
{
"span": {
"replace": [
{
"start": [
2,
1
],
"end": [
2,
5
]
},
{
"start": [
2,
1
],
"end": [
2,
2
]
}
]
},
"summary": "Replaced the 'zero' identifier with the 'a' identifier in the a variable"
},
{
"span": {
"replace": [
{
"start": [
3,
1
],
"end": [
3,
4
]
},
{
"start": [
3,
1
],
"end": [
3,
2
]
}
]
},
"summary": "Replaced the 'one' identifier with the 'b' identifier in the b variable"
}
]
},
"errors": {}
},
"filePaths": [
"grouped-var-declarations.go"
],
"patch": [
"diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
"index 5ed0e06..6b9c91d 100644",
"--- a/grouped-var-declarations.go",
"+++ b/grouped-var-declarations.go",
"@@ -1,6 +1,6 @@",
" var (",
"-zero = 0",
"-one = 1",
"+a = 0",
"+b = 1",
" )",
" var (",
" zero = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "25b8fae28eebfaaa5e88a04d68b10205a277ed91..34a449a972a1a710b5cd14ca0c174c15dcaeb003"
}
,{
"testCaseDescription": "go-grouped-var-declarations-delete-replacement-test",
"expectedResult": {
"changes": {
"grouped-var-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Deleted the 'zero' variable"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"grouped-var-declarations.go"
],
"patch": [
"diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
"index 6b9c91d..9094e82 100644",
"--- a/grouped-var-declarations.go",
"+++ b/grouped-var-declarations.go",
"@@ -1,12 +1,8 @@",
" var (",
"-a = 0",
"-b = 1",
"-)",
"-var (",
" zero = 0",
" one = 1",
" )",
" var (",
"-zero = 0",
"-one = 1",
"+a = 0",
"+b = 1",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "34a449a972a1a710b5cd14ca0c174c15dcaeb003..513b36b7a4797c5c95576f1bdcfe5c3aff699138"
}
,{
"testCaseDescription": "go-grouped-var-declarations-delete-test",
"expectedResult": {
"changes": {
"grouped-var-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'zero' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'one' variable"
}
]
},
"errors": {}
},
"filePaths": [
"grouped-var-declarations.go"
],
"patch": [
"diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
"index 9094e82..d954576 100644",
"--- a/grouped-var-declarations.go",
"+++ b/grouped-var-declarations.go",
"@@ -1,8 +1,4 @@",
" var (",
"-zero = 0",
"-one = 1",
"-)",
"-var (",
" a = 0",
" b = 1",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "513b36b7a4797c5c95576f1bdcfe5c3aff699138..b9336abbeeb3b7e8e18bd0757837c28f3d1b41e1"
}
,{
"testCaseDescription": "go-grouped-var-declarations-delete-rest-test",
"expectedResult": {
"changes": {
"grouped-var-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"grouped-var-declarations.go"
],
"patch": [
"diff --git a/grouped-var-declarations.go b/grouped-var-declarations.go",
"index d954576..e69de29 100644",
"--- a/grouped-var-declarations.go",
"+++ b/grouped-var-declarations.go",
"@@ -1,4 +0,0 @@",
"-var (",
"-a = 0",
"-b = 1",
"-)"
],
"gitDir": "test/corpus/repos/go",
"shas": "b9336abbeeb3b7e8e18bd0757837c28f3d1b41e1..25238a93bb3b92d4e2609c44f320e44fd9f4b537"
}]

View File

@ -0,0 +1,794 @@
[{
"testCaseDescription": "go-if-statements-insert-test",
"expectedResult": {
"changes": {
"if-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
3,
2
]
}
},
"summary": "Added the 'a()' if statement"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
6,
2
]
}
},
"summary": "Added the 'a := b(); c' if statement"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
11,
2
]
}
},
"summary": "Added the 'a()' if statement"
}
]
},
"errors": {}
},
"filePaths": [
"if-statements.go"
],
"patch": [
"diff --git a/if-statements.go b/if-statements.go",
"index e69de29..2266b8b 100644",
"--- a/if-statements.go",
"+++ b/if-statements.go",
"@@ -0,0 +1,11 @@",
"+if a() {",
"+b()",
"+}",
"+if a := b(); c {",
"+d()",
"+}",
"+if a() {",
"+b()",
"+} else {",
"+c()",
"+}"
],
"gitDir": "test/corpus/repos/go",
"shas": "4f9b8528a927a98cae35aa92a05bab432d2cf451..75f23c99193596d8ea69b9866cd03216408717d4"
}
,{
"testCaseDescription": "go-if-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"if-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
3,
2
]
}
},
"summary": "Added the 'x()' if statement"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
6,
2
]
}
},
"summary": "Added the 'y := b(); c' if statement"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
11,
2
]
}
},
"summary": "Added the 'z()' if statement"
},
{
"span": {
"insert": {
"start": [
12,
1
],
"end": [
14,
2
]
}
},
"summary": "Added the 'a()' if statement"
},
{
"span": {
"insert": {
"start": [
15,
1
],
"end": [
17,
2
]
}
},
"summary": "Added the 'a := b(); c' if statement"
},
{
"span": {
"insert": {
"start": [
18,
1
],
"end": [
22,
2
]
}
},
"summary": "Added the 'a()' if statement"
}
]
},
"errors": {}
},
"filePaths": [
"if-statements.go"
],
"patch": [
"diff --git a/if-statements.go b/if-statements.go",
"index 2266b8b..abacd6e 100644",
"--- a/if-statements.go",
"+++ b/if-statements.go",
"@@ -1,3 +1,25 @@",
"+if x() {",
"+b()",
"+}",
"+if y := b(); c {",
"+d()",
"+}",
"+if z() {",
"+b()",
"+} else {",
"+c()",
"+}",
"+if a() {",
"+b()",
"+}",
"+if a := b(); c {",
"+d()",
"+}",
"+if a() {",
"+b()",
"+} else {",
"+c()",
"+}",
" if a() {",
" b()",
" }"
],
"gitDir": "test/corpus/repos/go",
"shas": "75f23c99193596d8ea69b9866cd03216408717d4..669deded061b62b8d693268ec8535244bc3aeed8"
}
,{
"testCaseDescription": "go-if-statements-delete-insert-test",
"expectedResult": {
"changes": {
"if-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
4
],
"end": [
1,
5
]
},
{
"start": [
1,
4
],
"end": [
1,
5
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'a' identifier in the a() function call"
},
{
"span": {
"replace": [
{
"start": [
4,
4
],
"end": [
4,
5
]
},
{
"start": [
4,
4
],
"end": [
4,
5
]
}
]
},
"summary": "Replaced the 'y' identifier with the 'a' identifier in the a variable"
},
{
"span": {
"replace": [
{
"start": [
7,
4
],
"end": [
7,
5
]
},
{
"start": [
7,
4
],
"end": [
7,
5
]
}
]
},
"summary": "Replaced the 'z' identifier with the 'a' identifier in the a() function call"
}
]
},
"errors": {}
},
"filePaths": [
"if-statements.go"
],
"patch": [
"diff --git a/if-statements.go b/if-statements.go",
"index abacd6e..b5fd21a 100644",
"--- a/if-statements.go",
"+++ b/if-statements.go",
"@@ -1,10 +1,10 @@",
"-if x() {",
"+if a() {",
" b()",
" }",
"-if y := b(); c {",
"+if a := b(); c {",
" d()",
" }",
"-if z() {",
"+if a() {",
" b()",
" } else {",
" c()"
],
"gitDir": "test/corpus/repos/go",
"shas": "669deded061b62b8d693268ec8535244bc3aeed8..0ab3ed7afc3476fc761770f35bf7697971a2f839"
}
,{
"testCaseDescription": "go-if-statements-replacement-test",
"expectedResult": {
"changes": {
"if-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
4
],
"end": [
1,
5
]
},
{
"start": [
1,
4
],
"end": [
1,
5
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'x' identifier in the x() function call"
},
{
"span": {
"replace": [
{
"start": [
4,
4
],
"end": [
4,
5
]
},
{
"start": [
4,
4
],
"end": [
4,
5
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'y' identifier in the y variable"
},
{
"span": {
"replace": [
{
"start": [
7,
4
],
"end": [
7,
5
]
},
{
"start": [
7,
4
],
"end": [
7,
5
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'z' identifier in the z() function call"
}
]
},
"errors": {}
},
"filePaths": [
"if-statements.go"
],
"patch": [
"diff --git a/if-statements.go b/if-statements.go",
"index b5fd21a..abacd6e 100644",
"--- a/if-statements.go",
"+++ b/if-statements.go",
"@@ -1,10 +1,10 @@",
"-if a() {",
"+if x() {",
" b()",
" }",
"-if a := b(); c {",
"+if y := b(); c {",
" d()",
" }",
"-if a() {",
"+if z() {",
" b()",
" } else {",
" c()"
],
"gitDir": "test/corpus/repos/go",
"shas": "0ab3ed7afc3476fc761770f35bf7697971a2f839..2f24dc9616440294210032ea90d1869e7b39cc8c"
}
,{
"testCaseDescription": "go-if-statements-delete-replacement-test",
"expectedResult": {
"changes": {
"if-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
3,
2
]
}
},
"summary": "Deleted the 'x()' if statement"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
6,
2
]
}
},
"summary": "Deleted the 'y := b(); c' if statement"
},
{
"span": {
"delete": {
"start": [
7,
1
],
"end": [
11,
2
]
}
},
"summary": "Deleted the 'z()' if statement"
},
{
"span": {
"delete": {
"start": [
12,
1
],
"end": [
14,
2
]
}
},
"summary": "Deleted the 'a()' if statement"
},
{
"span": {
"delete": {
"start": [
15,
1
],
"end": [
17,
2
]
}
},
"summary": "Deleted the 'a := b(); c' if statement"
},
{
"span": {
"delete": {
"start": [
18,
1
],
"end": [
22,
2
]
}
},
"summary": "Deleted the 'a()' if statement"
},
{
"span": {
"insert": {
"start": [
12,
1
],
"end": [
14,
2
]
}
},
"summary": "Added the 'x()' if statement"
},
{
"span": {
"insert": {
"start": [
15,
1
],
"end": [
17,
2
]
}
},
"summary": "Added the 'y := b(); c' if statement"
},
{
"span": {
"insert": {
"start": [
18,
1
],
"end": [
22,
2
]
}
},
"summary": "Added the 'z()' if statement"
}
]
},
"errors": {}
},
"filePaths": [
"if-statements.go"
],
"patch": [
"diff --git a/if-statements.go b/if-statements.go",
"index abacd6e..ccb09fd 100644",
"--- a/if-statements.go",
"+++ b/if-statements.go",
"@@ -1,14 +1,3 @@",
"-if x() {",
"-b()",
"-}",
"-if y := b(); c {",
"-d()",
"-}",
"-if z() {",
"-b()",
"-} else {",
"-c()",
"-}",
" if a() {",
" b()",
" }",
"@@ -20,13 +9,13 @@ b()",
" } else {",
" c()",
" }",
"-if a() {",
"+if x() {",
" b()",
" }",
"-if a := b(); c {",
"+if y := b(); c {",
" d()",
" }",
"-if a() {",
"+if z() {",
" b()",
" } else {",
" c()"
],
"gitDir": "test/corpus/repos/go",
"shas": "2f24dc9616440294210032ea90d1869e7b39cc8c..dd27d3e8d9917d7970125a0e771840a3a352768d"
}
,{
"testCaseDescription": "go-if-statements-delete-test",
"expectedResult": {
"changes": {
"if-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
3,
2
]
}
},
"summary": "Deleted the 'a()' if statement"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
6,
2
]
}
},
"summary": "Deleted the 'a := b(); c' if statement"
},
{
"span": {
"delete": {
"start": [
7,
1
],
"end": [
11,
2
]
}
},
"summary": "Deleted the 'a()' if statement"
}
]
},
"errors": {}
},
"filePaths": [
"if-statements.go"
],
"patch": [
"diff --git a/if-statements.go b/if-statements.go",
"index ccb09fd..2e63573 100644",
"--- a/if-statements.go",
"+++ b/if-statements.go",
"@@ -1,14 +1,3 @@",
"-if a() {",
"-b()",
"-}",
"-if a := b(); c {",
"-d()",
"-}",
"-if a() {",
"-b()",
"-} else {",
"-c()",
"-}",
" if x() {",
" b()",
" }"
],
"gitDir": "test/corpus/repos/go",
"shas": "dd27d3e8d9917d7970125a0e771840a3a352768d..1559b8975147717c1d7eb9ae330d6bd4dbc18702"
}
,{
"testCaseDescription": "go-if-statements-delete-rest-test",
"expectedResult": {
"changes": {
"if-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
3,
2
]
}
},
"summary": "Deleted the 'x()' if statement"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
6,
2
]
}
},
"summary": "Deleted the 'y := b(); c' if statement"
},
{
"span": {
"delete": {
"start": [
7,
1
],
"end": [
11,
2
]
}
},
"summary": "Deleted the 'z()' if statement"
}
]
},
"errors": {}
},
"filePaths": [
"if-statements.go"
],
"patch": [
"diff --git a/if-statements.go b/if-statements.go",
"index 2e63573..e69de29 100644",
"--- a/if-statements.go",
"+++ b/if-statements.go",
"@@ -1,11 +0,0 @@",
"-if x() {",
"-b()",
"-}",
"-if y := b(); c {",
"-d()",
"-}",
"-if z() {",
"-b()",
"-} else {",
"-c()",
"-}"
],
"gitDir": "test/corpus/repos/go",
"shas": "1559b8975147717c1d7eb9ae330d6bd4dbc18702..d77b70cb3981afaf807f3e56652ecd386101cb2b"
}]

View File

@ -0,0 +1,560 @@
[{
"testCaseDescription": "go-imaginary-literals-insert-test",
"expectedResult": {
"changes": {
"imaginary-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"imaginary-literals.go"
],
"patch": [
"diff --git a/imaginary-literals.go b/imaginary-literals.go",
"index e69de29..aca2d55 100644",
"--- a/imaginary-literals.go",
"+++ b/imaginary-literals.go",
"@@ -0,0 +1,4 @@",
"+const (",
"+a = 01i",
"+b = 1.e+100i",
"+)"
],
"gitDir": "test/corpus/repos/go",
"shas": "9fd880a1842d8c0b0096899be831486a006f50e4..1dfc4de50a79b596b883a8c32478aed48332a96b"
}
,{
"testCaseDescription": "go-imaginary-literals-replacement-insert-test",
"expectedResult": {
"changes": {
"imaginary-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'b' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"imaginary-literals.go"
],
"patch": [
"diff --git a/imaginary-literals.go b/imaginary-literals.go",
"index aca2d55..6983988 100644",
"--- a/imaginary-literals.go",
"+++ b/imaginary-literals.go",
"@@ -1,4 +1,12 @@",
" const (",
"+a = 02i",
"+b = 1.e+103i",
"+)",
"+const (",
"+a = 01i",
"+b = 1.e+100i",
"+)",
"+const (",
" a = 01i",
" b = 1.e+100i",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "1dfc4de50a79b596b883a8c32478aed48332a96b..22a5dcc7eb910c4be07e0d79c4010014c87b9a45"
}
,{
"testCaseDescription": "go-imaginary-literals-delete-insert-test",
"expectedResult": {
"changes": {
"imaginary-literals.go": [
{
"span": {
"replace": [
{
"start": [
2,
5
],
"end": [
2,
8
]
},
{
"start": [
2,
5
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the '02i' imaginary_literal with the '01i' imaginary_literal in the a variable"
},
{
"span": {
"replace": [
{
"start": [
3,
5
],
"end": [
3,
13
]
},
{
"start": [
3,
5
],
"end": [
3,
13
]
}
]
},
"summary": "Replaced the '1.e+103i' imaginary_literal with the '1.e+100i' imaginary_literal in the b variable"
}
]
},
"errors": {}
},
"filePaths": [
"imaginary-literals.go"
],
"patch": [
"diff --git a/imaginary-literals.go b/imaginary-literals.go",
"index 6983988..a7e36a5 100644",
"--- a/imaginary-literals.go",
"+++ b/imaginary-literals.go",
"@@ -1,6 +1,6 @@",
" const (",
"-a = 02i",
"-b = 1.e+103i",
"+a = 01i",
"+b = 1.e+100i",
" )",
" const (",
" a = 01i"
],
"gitDir": "test/corpus/repos/go",
"shas": "22a5dcc7eb910c4be07e0d79c4010014c87b9a45..c8e821fccc1a9384008640b22a57896832df548d"
}
,{
"testCaseDescription": "go-imaginary-literals-replacement-test",
"expectedResult": {
"changes": {
"imaginary-literals.go": [
{
"span": {
"replace": [
{
"start": [
2,
5
],
"end": [
2,
8
]
},
{
"start": [
2,
5
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the '01i' imaginary_literal with the '02i' imaginary_literal in the a variable"
},
{
"span": {
"replace": [
{
"start": [
3,
5
],
"end": [
3,
13
]
},
{
"start": [
3,
5
],
"end": [
3,
13
]
}
]
},
"summary": "Replaced the '1.e+100i' imaginary_literal with the '1.e+103i' imaginary_literal in the b variable"
}
]
},
"errors": {}
},
"filePaths": [
"imaginary-literals.go"
],
"patch": [
"diff --git a/imaginary-literals.go b/imaginary-literals.go",
"index a7e36a5..6983988 100644",
"--- a/imaginary-literals.go",
"+++ b/imaginary-literals.go",
"@@ -1,6 +1,6 @@",
" const (",
"-a = 01i",
"-b = 1.e+100i",
"+a = 02i",
"+b = 1.e+103i",
" )",
" const (",
" a = 01i"
],
"gitDir": "test/corpus/repos/go",
"shas": "c8e821fccc1a9384008640b22a57896832df548d..d7c0cbbf7c636589fb8707bd044efc2a9c74ac77"
}
,{
"testCaseDescription": "go-imaginary-literals-delete-replacement-test",
"expectedResult": {
"changes": {
"imaginary-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"imaginary-literals.go"
],
"patch": [
"diff --git a/imaginary-literals.go b/imaginary-literals.go",
"index 6983988..02cff8d 100644",
"--- a/imaginary-literals.go",
"+++ b/imaginary-literals.go",
"@@ -1,12 +1,8 @@",
" const (",
"-a = 02i",
"-b = 1.e+103i",
"-)",
"-const (",
" a = 01i",
" b = 1.e+100i",
" )",
" const (",
"-a = 01i",
"-b = 1.e+100i",
"+a = 02i",
"+b = 1.e+103i",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "d7c0cbbf7c636589fb8707bd044efc2a9c74ac77..693f96d6dd713a80868ba814289fcf23a9542611"
}
,{
"testCaseDescription": "go-imaginary-literals-delete-test",
"expectedResult": {
"changes": {
"imaginary-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"imaginary-literals.go"
],
"patch": [
"diff --git a/imaginary-literals.go b/imaginary-literals.go",
"index 02cff8d..6d8ec55 100644",
"--- a/imaginary-literals.go",
"+++ b/imaginary-literals.go",
"@@ -1,8 +1,4 @@",
" const (",
"-a = 01i",
"-b = 1.e+100i",
"-)",
"-const (",
" a = 02i",
" b = 1.e+103i",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "693f96d6dd713a80868ba814289fcf23a9542611..ea50813182b228c1202b76c8c102a8156732e30a"
}
,{
"testCaseDescription": "go-imaginary-literals-delete-rest-test",
"expectedResult": {
"changes": {
"imaginary-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"imaginary-literals.go"
],
"patch": [
"diff --git a/imaginary-literals.go b/imaginary-literals.go",
"index 6d8ec55..e69de29 100644",
"--- a/imaginary-literals.go",
"+++ b/imaginary-literals.go",
"@@ -1,4 +0,0 @@",
"-const (",
"-a = 02i",
"-b = 1.e+103i",
"-)"
],
"gitDir": "test/corpus/repos/go",
"shas": "ea50813182b228c1202b76c8c102a8156732e30a..740c6c6b1390c86d2f179d9d31f010916292861a"
}]

View File

@ -0,0 +1,544 @@
[{
"testCaseDescription": "go-increment-decrement-statements-insert-test",
"expectedResult": {
"changes": {
"increment-decrement-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
2
]
}
},
"summary": "Added the 'i' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
2
]
}
},
"summary": "Added the 'j' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"increment-decrement-statements.go"
],
"patch": [
"diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
"index e69de29..c118f41 100644",
"--- a/increment-decrement-statements.go",
"+++ b/increment-decrement-statements.go",
"@@ -0,0 +1,2 @@",
"+i++",
"+j--"
],
"gitDir": "test/corpus/repos/go",
"shas": "927f995f9a27002e1694b5d3ce66a7dbbfda6720..08e1c1af15a7a2e6b3905900905a1fd79d6f1c43"
}
,{
"testCaseDescription": "go-increment-decrement-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"increment-decrement-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Added the 'foo' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
2
]
}
},
"summary": "Added the 'x' identifier"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
2
]
}
},
"summary": "Added the 'i' identifier"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'j' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"increment-decrement-statements.go"
],
"patch": [
"diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
"index c118f41..d617bc4 100644",
"--- a/increment-decrement-statements.go",
"+++ b/increment-decrement-statements.go",
"@@ -1,2 +1,6 @@",
"+foo++",
"+x++",
"+i++",
"+j--",
" i++",
" j--"
],
"gitDir": "test/corpus/repos/go",
"shas": "08e1c1af15a7a2e6b3905900905a1fd79d6f1c43..ce7abe0a0dbc3a4f0c453bba572432d0ed745d36"
}
,{
"testCaseDescription": "go-increment-decrement-statements-delete-insert-test",
"expectedResult": {
"changes": {
"increment-decrement-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
4
]
},
{
"start": [
1,
1
],
"end": [
1,
2
]
}
]
},
"summary": "Replaced the 'foo' identifier with the 'i' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
2
]
}
},
"summary": "Added the 'j' identifier"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
2
]
}
},
"summary": "Deleted the 'x' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"increment-decrement-statements.go"
],
"patch": [
"diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
"index d617bc4..15214d0 100644",
"--- a/increment-decrement-statements.go",
"+++ b/increment-decrement-statements.go",
"@@ -1,5 +1,5 @@",
"-foo++",
"-x++",
"+i++",
"+j--",
" i++",
" j--",
" i++"
],
"gitDir": "test/corpus/repos/go",
"shas": "ce7abe0a0dbc3a4f0c453bba572432d0ed745d36..0fd355f46a4c9aec73e9874645e7a89d920e58e3"
}
,{
"testCaseDescription": "go-increment-decrement-statements-replacement-test",
"expectedResult": {
"changes": {
"increment-decrement-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
2
]
},
{
"start": [
1,
1
],
"end": [
1,
4
]
}
]
},
"summary": "Replaced the 'i' identifier with the 'foo' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
2
]
}
},
"summary": "Added the 'x' identifier"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
2
]
}
},
"summary": "Deleted the 'j' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"increment-decrement-statements.go"
],
"patch": [
"diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
"index 15214d0..d617bc4 100644",
"--- a/increment-decrement-statements.go",
"+++ b/increment-decrement-statements.go",
"@@ -1,5 +1,5 @@",
"-i++",
"-j--",
"+foo++",
"+x++",
" i++",
" j--",
" i++"
],
"gitDir": "test/corpus/repos/go",
"shas": "0fd355f46a4c9aec73e9874645e7a89d920e58e3..628555688b52d8b03b5a7efa9fd07954f93c04fd"
}
,{
"testCaseDescription": "go-increment-decrement-statements-delete-replacement-test",
"expectedResult": {
"changes": {
"increment-decrement-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Deleted the 'foo' identifier"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
2
]
}
},
"summary": "Deleted the 'x' identifier"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
2
]
}
},
"summary": "Deleted the 'i' identifier"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'j' identifier"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
4
]
}
},
"summary": "Added the 'foo' identifier"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'x' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"increment-decrement-statements.go"
],
"patch": [
"diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
"index d617bc4..640bbf1 100644",
"--- a/increment-decrement-statements.go",
"+++ b/increment-decrement-statements.go",
"@@ -1,6 +1,4 @@",
"-foo++",
"-x++",
"-i++",
"-j--",
" i++",
" j--",
"+foo++",
"+x++"
],
"gitDir": "test/corpus/repos/go",
"shas": "628555688b52d8b03b5a7efa9fd07954f93c04fd..4df0db28123dab35f85c9f8c5f3f6045a9913354"
}
,{
"testCaseDescription": "go-increment-decrement-statements-delete-test",
"expectedResult": {
"changes": {
"increment-decrement-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
2
]
}
},
"summary": "Deleted the 'i' identifier"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
2
]
}
},
"summary": "Deleted the 'j' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"increment-decrement-statements.go"
],
"patch": [
"diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
"index 640bbf1..b7c351d 100644",
"--- a/increment-decrement-statements.go",
"+++ b/increment-decrement-statements.go",
"@@ -1,4 +1,2 @@",
"-i++",
"-j--",
" foo++",
" x++"
],
"gitDir": "test/corpus/repos/go",
"shas": "4df0db28123dab35f85c9f8c5f3f6045a9913354..f328fdb9b4ab03a8667cbcafaaf2ef18c667ac57"
}
,{
"testCaseDescription": "go-increment-decrement-statements-delete-rest-test",
"expectedResult": {
"changes": {
"increment-decrement-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Deleted the 'foo' identifier"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
2
]
}
},
"summary": "Deleted the 'x' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"increment-decrement-statements.go"
],
"patch": [
"diff --git a/increment-decrement-statements.go b/increment-decrement-statements.go",
"index b7c351d..e69de29 100644",
"--- a/increment-decrement-statements.go",
"+++ b/increment-decrement-statements.go",
"@@ -1,2 +0,0 @@",
"-foo++",
"-x++"
],
"gitDir": "test/corpus/repos/go",
"shas": "f328fdb9b4ab03a8667cbcafaaf2ef18c667ac57..a5b8a6804181af3a1387f9a23e3f85c44ddb6082"
}]

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,371 @@
[{
"testCaseDescription": "go-label-statements-insert-test",
"expectedResult": {
"changes": {
"label-statements.go": [
{
"span": {
"insert": {
"start": [
2,
3
],
"end": [
2,
15
]
}
},
"summary": "Added the 'insert_label' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"label-statements.go"
],
"patch": [
"diff --git a/label-statements.go b/label-statements.go",
"index e69de29..d0544fe 100644",
"--- a/label-statements.go",
"+++ b/label-statements.go",
"@@ -0,0 +1,3 @@",
"+{",
"+ insert_label:",
"+}"
],
"gitDir": "test/corpus/repos/go",
"shas": "13fa148e00739eba43f10562e024e15d2fc7e5d9..ec940835e3aadb604515bf67c883ca6521cb2d08"
}
,{
"testCaseDescription": "go-label-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"label-statements.go": [
{
"span": {
"insert": {
"start": [
2,
3
],
"end": [
2,
20
]
}
},
"summary": "Added the 'replacement_label' identifier"
},
{
"span": {
"insert": {
"start": [
5,
3
],
"end": [
5,
15
]
}
},
"summary": "Added the 'insert_label' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"label-statements.go"
],
"patch": [
"diff --git a/label-statements.go b/label-statements.go",
"index d0544fe..745311d 100644",
"--- a/label-statements.go",
"+++ b/label-statements.go",
"@@ -1,3 +1,9 @@",
" {",
"+ replacement_label:",
"+}",
"+{",
"+ insert_label:",
"+}",
"+{",
" insert_label:",
" }"
],
"gitDir": "test/corpus/repos/go",
"shas": "ec940835e3aadb604515bf67c883ca6521cb2d08..5e455b8924d22fe892b8bab4970fc6524c4deefc"
}
,{
"testCaseDescription": "go-label-statements-delete-insert-test",
"expectedResult": {
"changes": {
"label-statements.go": [
{
"span": {
"replace": [
{
"start": [
2,
3
],
"end": [
2,
20
]
},
{
"start": [
2,
3
],
"end": [
2,
15
]
}
]
},
"summary": "Replaced the 'replacement_label' identifier with the 'insert_label' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"label-statements.go"
],
"patch": [
"diff --git a/label-statements.go b/label-statements.go",
"index 745311d..be34b5c 100644",
"--- a/label-statements.go",
"+++ b/label-statements.go",
"@@ -1,5 +1,5 @@",
" {",
"- replacement_label:",
"+ insert_label:",
" }",
" {",
" insert_label:"
],
"gitDir": "test/corpus/repos/go",
"shas": "5e455b8924d22fe892b8bab4970fc6524c4deefc..8a5a495c2571e6547c42e532abcb5a9f3aec4024"
}
,{
"testCaseDescription": "go-label-statements-replacement-test",
"expectedResult": {
"changes": {
"label-statements.go": [
{
"span": {
"replace": [
{
"start": [
2,
3
],
"end": [
2,
15
]
},
{
"start": [
2,
3
],
"end": [
2,
20
]
}
]
},
"summary": "Replaced the 'insert_label' identifier with the 'replacement_label' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"label-statements.go"
],
"patch": [
"diff --git a/label-statements.go b/label-statements.go",
"index be34b5c..745311d 100644",
"--- a/label-statements.go",
"+++ b/label-statements.go",
"@@ -1,5 +1,5 @@",
" {",
"- insert_label:",
"+ replacement_label:",
" }",
" {",
" insert_label:"
],
"gitDir": "test/corpus/repos/go",
"shas": "8a5a495c2571e6547c42e532abcb5a9f3aec4024..22c8014919ec0c0808de5aad53da258e151ed475"
}
,{
"testCaseDescription": "go-label-statements-delete-replacement-test",
"expectedResult": {
"changes": {
"label-statements.go": [
{
"span": {
"delete": {
"start": [
2,
3
],
"end": [
2,
20
]
}
},
"summary": "Deleted the 'replacement_label' identifier"
},
{
"span": {
"delete": {
"start": [
5,
3
],
"end": [
5,
15
]
}
},
"summary": "Deleted the 'insert_label' identifier"
},
{
"span": {
"insert": {
"start": [
5,
3
],
"end": [
5,
20
]
}
},
"summary": "Added the 'replacement_label' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"label-statements.go"
],
"patch": [
"diff --git a/label-statements.go b/label-statements.go",
"index 745311d..57f6c03 100644",
"--- a/label-statements.go",
"+++ b/label-statements.go",
"@@ -1,9 +1,6 @@",
" {",
"- replacement_label:",
"-}",
"-{",
" insert_label:",
" }",
" {",
"- insert_label:",
"+ replacement_label:",
" }"
],
"gitDir": "test/corpus/repos/go",
"shas": "22c8014919ec0c0808de5aad53da258e151ed475..6cab5df3eecd3e4b9cde037c1d0d63c733be9b25"
}
,{
"testCaseDescription": "go-label-statements-delete-test",
"expectedResult": {
"changes": {
"label-statements.go": [
{
"span": {
"delete": {
"start": [
2,
3
],
"end": [
2,
15
]
}
},
"summary": "Deleted the 'insert_label' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"label-statements.go"
],
"patch": [
"diff --git a/label-statements.go b/label-statements.go",
"index 57f6c03..6920e65 100644",
"--- a/label-statements.go",
"+++ b/label-statements.go",
"@@ -1,6 +1,3 @@",
" {",
"- insert_label:",
"-}",
"-{",
" replacement_label:",
" }"
],
"gitDir": "test/corpus/repos/go",
"shas": "6cab5df3eecd3e4b9cde037c1d0d63c733be9b25..66df55101e51883709ed9932d216cb965d9bef49"
}
,{
"testCaseDescription": "go-label-statements-delete-rest-test",
"expectedResult": {
"changes": {
"label-statements.go": [
{
"span": {
"delete": {
"start": [
2,
3
],
"end": [
2,
20
]
}
},
"summary": "Deleted the 'replacement_label' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"label-statements.go"
],
"patch": [
"diff --git a/label-statements.go b/label-statements.go",
"index 6920e65..e69de29 100644",
"--- a/label-statements.go",
"+++ b/label-statements.go",
"@@ -1,3 +0,0 @@",
"-{",
"- replacement_label:",
"-}"
],
"gitDir": "test/corpus/repos/go",
"shas": "66df55101e51883709ed9932d216cb965d9bef49..d2477a592fdd731c7bb7e1b1d1fe4b3b87939257"
}]

View File

@ -0,0 +1,585 @@
[{
"testCaseDescription": "go-map-literals-insert-test",
"expectedResult": {
"changes": {
"map-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 's' variable"
}
]
},
"errors": {}
},
"filePaths": [
"map-literals.go"
],
"patch": [
"diff --git a/map-literals.go b/map-literals.go",
"index e69de29..16fb3cf 100644",
"--- a/map-literals.go",
"+++ b/map-literals.go",
"@@ -0,0 +1,4 @@",
"+const s = map[string]string{",
"+\"hi\": \"hello\",",
"+\"bye\": \"goodbye\",",
"+}"
],
"gitDir": "test/corpus/repos/go",
"shas": "f366494a187af73e7fcf6d60c2aa3bb503543f80..e925ebba0abf3bdf2a84d3a66d52bd0380796809"
}
,{
"testCaseDescription": "go-map-literals-replacement-insert-test",
"expectedResult": {
"changes": {
"map-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 's' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 's' variable"
}
]
},
"errors": {}
},
"filePaths": [
"map-literals.go"
],
"patch": [
"diff --git a/map-literals.go b/map-literals.go",
"index 16fb3cf..b3c30ca 100644",
"--- a/map-literals.go",
"+++ b/map-literals.go",
"@@ -1,3 +1,11 @@",
"+const s = map[string]int{",
"+\"foo\": \"bar\",",
"+\"baz\": \"hello\",",
"+}",
"+const s = map[string]string{",
"+\"hi\": \"hello\",",
"+\"bye\": \"goodbye\",",
"+}",
" const s = map[string]string{",
" \"hi\": \"hello\",",
" \"bye\": \"goodbye\","
],
"gitDir": "test/corpus/repos/go",
"shas": "e925ebba0abf3bdf2a84d3a66d52bd0380796809..de28fc5f9c2b25ec7ae4a2a30d8a7edc342a76bb"
}
,{
"testCaseDescription": "go-map-literals-delete-insert-test",
"expectedResult": {
"changes": {
"map-literals.go": [
{
"span": {
"replace": [
{
"start": [
1,
22
],
"end": [
1,
25
]
},
{
"start": [
1,
15
],
"end": [
1,
21
]
}
]
},
"summary": "Replaced the 'int' identifier with the 'string' identifier in the s variable"
},
{
"span": {
"replace": [
{
"start": [
2,
1
],
"end": [
2,
6
]
},
{
"start": [
2,
1
],
"end": [
2,
5
]
}
]
},
"summary": "Replaced the \"foo\" string with the \"hi\" string in the s variable"
},
{
"span": {
"replace": [
{
"start": [
2,
8
],
"end": [
2,
13
]
},
{
"start": [
2,
7
],
"end": [
2,
14
]
}
]
},
"summary": "Replaced the \"bar\" string with the \"hello\" string in the s variable"
},
{
"span": {
"replace": [
{
"start": [
3,
1
],
"end": [
3,
6
]
},
{
"start": [
3,
1
],
"end": [
3,
6
]
}
]
},
"summary": "Replaced the \"baz\" string with the \"bye\" string in the s variable"
},
{
"span": {
"replace": [
{
"start": [
3,
8
],
"end": [
3,
15
]
},
{
"start": [
3,
8
],
"end": [
3,
17
]
}
]
},
"summary": "Replaced the \"hello\" string with the \"goodbye\" string in the s variable"
}
]
},
"errors": {}
},
"filePaths": [
"map-literals.go"
],
"patch": [
"diff --git a/map-literals.go b/map-literals.go",
"index b3c30ca..72c2e91 100644",
"--- a/map-literals.go",
"+++ b/map-literals.go",
"@@ -1,6 +1,6 @@",
"-const s = map[string]int{",
"-\"foo\": \"bar\",",
"-\"baz\": \"hello\",",
"+const s = map[string]string{",
"+\"hi\": \"hello\",",
"+\"bye\": \"goodbye\",",
" }",
" const s = map[string]string{",
" \"hi\": \"hello\","
],
"gitDir": "test/corpus/repos/go",
"shas": "de28fc5f9c2b25ec7ae4a2a30d8a7edc342a76bb..db595e9471ff2fef089dc2aa7f502568d1502a6a"
}
,{
"testCaseDescription": "go-map-literals-replacement-test",
"expectedResult": {
"changes": {
"map-literals.go": [
{
"span": {
"delete": {
"start": [
1,
15
],
"end": [
1,
21
]
}
},
"summary": "Deleted the 'string' identifier in the s variable"
},
{
"span": {
"insert": {
"start": [
1,
22
],
"end": [
1,
25
]
}
},
"summary": "Added the 'int' identifier in the s variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
6
]
}
},
"summary": "Added the \"foo\" string in the s variable"
},
{
"span": {
"insert": {
"start": [
2,
8
],
"end": [
2,
13
]
}
},
"summary": "Added the \"bar\" string in the s variable"
},
{
"span": {
"replace": [
{
"start": [
2,
1
],
"end": [
2,
5
]
},
{
"start": [
3,
1
],
"end": [
3,
6
]
}
]
},
"summary": "Replaced the \"hi\" string with the \"baz\" string in the s variable"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
6
]
}
},
"summary": "Deleted the \"bye\" string in the s variable"
},
{
"span": {
"delete": {
"start": [
3,
8
],
"end": [
3,
17
]
}
},
"summary": "Deleted the \"goodbye\" string in the s variable"
}
]
},
"errors": {}
},
"filePaths": [
"map-literals.go"
],
"patch": [
"diff --git a/map-literals.go b/map-literals.go",
"index 72c2e91..b3c30ca 100644",
"--- a/map-literals.go",
"+++ b/map-literals.go",
"@@ -1,6 +1,6 @@",
"-const s = map[string]string{",
"-\"hi\": \"hello\",",
"-\"bye\": \"goodbye\",",
"+const s = map[string]int{",
"+\"foo\": \"bar\",",
"+\"baz\": \"hello\",",
" }",
" const s = map[string]string{",
" \"hi\": \"hello\","
],
"gitDir": "test/corpus/repos/go",
"shas": "db595e9471ff2fef089dc2aa7f502568d1502a6a..a7fd4cda280bf4ae44d7ada58ada52f350017735"
}
,{
"testCaseDescription": "go-map-literals-delete-replacement-test",
"expectedResult": {
"changes": {
"map-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 's' variable"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Deleted the 's' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 's' variable"
}
]
},
"errors": {}
},
"filePaths": [
"map-literals.go"
],
"patch": [
"diff --git a/map-literals.go b/map-literals.go",
"index b3c30ca..6d5f577 100644",
"--- a/map-literals.go",
"+++ b/map-literals.go",
"@@ -1,12 +1,8 @@",
"-const s = map[string]int{",
"-\"foo\": \"bar\",",
"-\"baz\": \"hello\",",
"-}",
" const s = map[string]string{",
" \"hi\": \"hello\",",
" \"bye\": \"goodbye\",",
" }",
"-const s = map[string]string{",
"-\"hi\": \"hello\",",
"-\"bye\": \"goodbye\",",
"+const s = map[string]int{",
"+\"foo\": \"bar\",",
"+\"baz\": \"hello\",",
" }"
],
"gitDir": "test/corpus/repos/go",
"shas": "a7fd4cda280bf4ae44d7ada58ada52f350017735..c67615be6903f594bbda655de325f090b44a779e"
}
,{
"testCaseDescription": "go-map-literals-delete-test",
"expectedResult": {
"changes": {
"map-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 's' variable"
}
]
},
"errors": {}
},
"filePaths": [
"map-literals.go"
],
"patch": [
"diff --git a/map-literals.go b/map-literals.go",
"index 6d5f577..7f8e649 100644",
"--- a/map-literals.go",
"+++ b/map-literals.go",
"@@ -1,7 +1,3 @@",
"-const s = map[string]string{",
"-\"hi\": \"hello\",",
"-\"bye\": \"goodbye\",",
"-}",
" const s = map[string]int{",
" \"foo\": \"bar\",",
" \"baz\": \"hello\","
],
"gitDir": "test/corpus/repos/go",
"shas": "c67615be6903f594bbda655de325f090b44a779e..1c5da0b334e2c57d642798de8f4554d4e5d7e8b9"
}
,{
"testCaseDescription": "go-map-literals-delete-rest-test",
"expectedResult": {
"changes": {
"map-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 's' variable"
}
]
},
"errors": {}
},
"filePaths": [
"map-literals.go"
],
"patch": [
"diff --git a/map-literals.go b/map-literals.go",
"index 7f8e649..e69de29 100644",
"--- a/map-literals.go",
"+++ b/map-literals.go",
"@@ -1,4 +0,0 @@",
"-const s = map[string]int{",
"-\"foo\": \"bar\",",
"-\"baz\": \"hello\",",
"-}"
],
"gitDir": "test/corpus/repos/go",
"shas": "1c5da0b334e2c57d642798de8f4554d4e5d7e8b9..821d52811675ea17dd00d79b0f4e082376b97afc"
}]

View File

@ -0,0 +1,587 @@
[{
"testCaseDescription": "go-map-types-insert-test",
"expectedResult": {
"changes": {
"map-types.go": [
{
"span": {
"insert": {
"start": [
1,
6
],
"end": [
1,
8
]
}
},
"summary": "Added the 'm1' identifier"
},
{
"span": {
"insert": {
"start": [
1,
13
],
"end": [
1,
19
]
}
},
"summary": "Added the 'string' identifier"
},
{
"span": {
"insert": {
"start": [
1,
20
],
"end": [
1,
25
]
}
},
"summary": "Added the 'error' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"map-types.go"
],
"patch": [
"diff --git a/map-types.go b/map-types.go",
"index e69de29..c86220d 100644",
"--- a/map-types.go",
"+++ b/map-types.go",
"@@ -0,0 +1 @@",
"+type m1 map[string]error"
],
"gitDir": "test/corpus/repos/go",
"shas": "26e4335c9f693f66513cac8f6c4399a4fc45ad1b..728bb866043561cbbdc1e2b9db04ac55e14bd2fe"
}
,{
"testCaseDescription": "go-map-types-replacement-insert-test",
"expectedResult": {
"changes": {
"map-types.go": [
{
"span": {
"insert": {
"start": [
1,
6
],
"end": [
1,
8
]
}
},
"summary": "Added the 'm1' identifier"
},
{
"span": {
"insert": {
"start": [
1,
13
],
"end": [
1,
16
]
}
},
"summary": "Added the 'int' identifier"
},
{
"span": {
"insert": {
"start": [
1,
17
],
"end": [
1,
22
]
}
},
"summary": "Added the 'error' identifier"
},
{
"span": {
"insert": {
"start": [
2,
6
],
"end": [
2,
8
]
}
},
"summary": "Added the 'm1' identifier"
},
{
"span": {
"insert": {
"start": [
2,
13
],
"end": [
2,
19
]
}
},
"summary": "Added the 'string' identifier"
},
{
"span": {
"insert": {
"start": [
2,
20
],
"end": [
2,
25
]
}
},
"summary": "Added the 'error' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"map-types.go"
],
"patch": [
"diff --git a/map-types.go b/map-types.go",
"index c86220d..9cc2e8b 100644",
"--- a/map-types.go",
"+++ b/map-types.go",
"@@ -1 +1,3 @@",
"+type m1 map[int]error",
"+type m1 map[string]error",
" type m1 map[string]error"
],
"gitDir": "test/corpus/repos/go",
"shas": "728bb866043561cbbdc1e2b9db04ac55e14bd2fe..354b111d5e50ea7cca50e6dd82d6a096bb4dc043"
}
,{
"testCaseDescription": "go-map-types-delete-insert-test",
"expectedResult": {
"changes": {
"map-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
13
],
"end": [
1,
16
]
},
{
"start": [
1,
13
],
"end": [
1,
19
]
}
]
},
"summary": "Replaced the 'int' identifier with the 'string' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"map-types.go"
],
"patch": [
"diff --git a/map-types.go b/map-types.go",
"index 9cc2e8b..ee1d5a0 100644",
"--- a/map-types.go",
"+++ b/map-types.go",
"@@ -1,3 +1,3 @@",
"-type m1 map[int]error",
"+type m1 map[string]error",
" type m1 map[string]error",
" type m1 map[string]error"
],
"gitDir": "test/corpus/repos/go",
"shas": "354b111d5e50ea7cca50e6dd82d6a096bb4dc043..8d18ca22d7735a4d4ec15aaa47bb3f6f3cc31d43"
}
,{
"testCaseDescription": "go-map-types-replacement-test",
"expectedResult": {
"changes": {
"map-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
13
],
"end": [
1,
19
]
},
{
"start": [
1,
13
],
"end": [
1,
16
]
}
]
},
"summary": "Replaced the 'string' identifier with the 'int' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"map-types.go"
],
"patch": [
"diff --git a/map-types.go b/map-types.go",
"index ee1d5a0..9cc2e8b 100644",
"--- a/map-types.go",
"+++ b/map-types.go",
"@@ -1,3 +1,3 @@",
"-type m1 map[string]error",
"+type m1 map[int]error",
" type m1 map[string]error",
" type m1 map[string]error"
],
"gitDir": "test/corpus/repos/go",
"shas": "8d18ca22d7735a4d4ec15aaa47bb3f6f3cc31d43..f39a4aa0643801fca32ef454238ad77644439dab"
}
,{
"testCaseDescription": "go-map-types-delete-replacement-test",
"expectedResult": {
"changes": {
"map-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'm1' identifier"
},
{
"span": {
"delete": {
"start": [
1,
13
],
"end": [
1,
16
]
}
},
"summary": "Deleted the 'int' identifier"
},
{
"span": {
"delete": {
"start": [
1,
17
],
"end": [
1,
22
]
}
},
"summary": "Deleted the 'error' identifier"
},
{
"span": {
"delete": {
"start": [
2,
6
],
"end": [
2,
8
]
}
},
"summary": "Deleted the 'm1' identifier"
},
{
"span": {
"delete": {
"start": [
2,
13
],
"end": [
2,
19
]
}
},
"summary": "Deleted the 'string' identifier"
},
{
"span": {
"delete": {
"start": [
2,
20
],
"end": [
2,
25
]
}
},
"summary": "Deleted the 'error' identifier"
},
{
"span": {
"insert": {
"start": [
2,
6
],
"end": [
2,
8
]
}
},
"summary": "Added the 'm1' identifier"
},
{
"span": {
"insert": {
"start": [
2,
13
],
"end": [
2,
16
]
}
},
"summary": "Added the 'int' identifier"
},
{
"span": {
"insert": {
"start": [
2,
17
],
"end": [
2,
22
]
}
},
"summary": "Added the 'error' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"map-types.go"
],
"patch": [
"diff --git a/map-types.go b/map-types.go",
"index 9cc2e8b..a863ca9 100644",
"--- a/map-types.go",
"+++ b/map-types.go",
"@@ -1,3 +1,2 @@",
"-type m1 map[int]error",
"-type m1 map[string]error",
" type m1 map[string]error",
"+type m1 map[int]error"
],
"gitDir": "test/corpus/repos/go",
"shas": "f39a4aa0643801fca32ef454238ad77644439dab..103b721414de3bbad2adbe781738973424c8e468"
}
,{
"testCaseDescription": "go-map-types-delete-test",
"expectedResult": {
"changes": {
"map-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'm1' identifier"
},
{
"span": {
"delete": {
"start": [
1,
13
],
"end": [
1,
19
]
}
},
"summary": "Deleted the 'string' identifier"
},
{
"span": {
"delete": {
"start": [
1,
20
],
"end": [
1,
25
]
}
},
"summary": "Deleted the 'error' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"map-types.go"
],
"patch": [
"diff --git a/map-types.go b/map-types.go",
"index a863ca9..d7e6949 100644",
"--- a/map-types.go",
"+++ b/map-types.go",
"@@ -1,2 +1 @@",
"-type m1 map[string]error",
" type m1 map[int]error"
],
"gitDir": "test/corpus/repos/go",
"shas": "103b721414de3bbad2adbe781738973424c8e468..ac2d072f1c3048451e824aaf604dcda59c62c4a3"
}
,{
"testCaseDescription": "go-map-types-delete-rest-test",
"expectedResult": {
"changes": {
"map-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'm1' identifier"
},
{
"span": {
"delete": {
"start": [
1,
13
],
"end": [
1,
16
]
}
},
"summary": "Deleted the 'int' identifier"
},
{
"span": {
"delete": {
"start": [
1,
17
],
"end": [
1,
22
]
}
},
"summary": "Deleted the 'error' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"map-types.go"
],
"patch": [
"diff --git a/map-types.go b/map-types.go",
"index d7e6949..e69de29 100644",
"--- a/map-types.go",
"+++ b/map-types.go",
"@@ -1 +0,0 @@",
"-type m1 map[int]error"
],
"gitDir": "test/corpus/repos/go",
"shas": "ac2d072f1c3048451e824aaf604dcda59c62c4a3..3cf1fd2c498440d58dd5df34a4f217c00efa71b1"
}]

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,800 @@
[{
"testCaseDescription": "go-pointer-types-insert-test",
"expectedResult": {
"changes": {
"pointer-types.go": [
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
3
]
}
},
"summary": "Added the 'p1' identifier"
},
{
"span": {
"insert": {
"start": [
2,
5
],
"end": [
2,
11
]
}
},
"summary": "Added the 'string' identifier"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
3
]
}
},
"summary": "Added the 'p2' identifier"
},
{
"span": {
"insert": {
"start": [
3,
6
],
"end": [
3,
8
]
}
},
"summary": "Added the 'p1' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"pointer-types.go"
],
"patch": [
"diff --git a/pointer-types.go b/pointer-types.go",
"index e69de29..05b4659 100644",
"--- a/pointer-types.go",
"+++ b/pointer-types.go",
"@@ -0,0 +1,4 @@",
"+type (",
"+p1 *string",
"+p2 **p1",
"+)"
],
"gitDir": "test/corpus/repos/go",
"shas": "3cf1fd2c498440d58dd5df34a4f217c00efa71b1..cff34d9b4f8663f9e2a85316a00629c162eaab24"
}
,{
"testCaseDescription": "go-pointer-types-replacement-insert-test",
"expectedResult": {
"changes": {
"pointer-types.go": [
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
3
]
}
},
"summary": "Added the 'p1' identifier"
},
{
"span": {
"insert": {
"start": [
2,
5
],
"end": [
2,
8
]
}
},
"summary": "Added the 'int' identifier"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
3
]
}
},
"summary": "Added the 'p2' identifier"
},
{
"span": {
"insert": {
"start": [
3,
6
],
"end": [
3,
8
]
}
},
"summary": "Added the 'p3' identifier"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
3
]
}
},
"summary": "Added the 'p1' identifier"
},
{
"span": {
"insert": {
"start": [
6,
5
],
"end": [
6,
11
]
}
},
"summary": "Added the 'string' identifier"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
7,
3
]
}
},
"summary": "Added the 'p2' identifier"
},
{
"span": {
"insert": {
"start": [
7,
6
],
"end": [
7,
8
]
}
},
"summary": "Added the 'p1' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"pointer-types.go"
],
"patch": [
"diff --git a/pointer-types.go b/pointer-types.go",
"index 05b4659..95e685d 100644",
"--- a/pointer-types.go",
"+++ b/pointer-types.go",
"@@ -1,4 +1,12 @@",
" type (",
"+p1 *int",
"+p2 **p3",
"+)",
"+type (",
"+p1 *string",
"+p2 **p1",
"+)",
"+type (",
" p1 *string",
" p2 **p1",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "cff34d9b4f8663f9e2a85316a00629c162eaab24..0a00ceceb6353a9970f1aa9ced5771b5b21883c6"
}
,{
"testCaseDescription": "go-pointer-types-delete-insert-test",
"expectedResult": {
"changes": {
"pointer-types.go": [
{
"span": {
"replace": [
{
"start": [
2,
5
],
"end": [
2,
8
]
},
{
"start": [
2,
5
],
"end": [
2,
11
]
}
]
},
"summary": "Replaced the 'int' identifier with the 'string' identifier"
},
{
"span": {
"replace": [
{
"start": [
3,
6
],
"end": [
3,
8
]
},
{
"start": [
3,
6
],
"end": [
3,
8
]
}
]
},
"summary": "Replaced the 'p3' identifier with the 'p1' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"pointer-types.go"
],
"patch": [
"diff --git a/pointer-types.go b/pointer-types.go",
"index 95e685d..74ff673 100644",
"--- a/pointer-types.go",
"+++ b/pointer-types.go",
"@@ -1,6 +1,6 @@",
" type (",
"-p1 *int",
"-p2 **p3",
"+p1 *string",
"+p2 **p1",
" )",
" type (",
" p1 *string"
],
"gitDir": "test/corpus/repos/go",
"shas": "0a00ceceb6353a9970f1aa9ced5771b5b21883c6..2f99a01b337c02263ca4e9399902b16aaba1dedf"
}
,{
"testCaseDescription": "go-pointer-types-replacement-test",
"expectedResult": {
"changes": {
"pointer-types.go": [
{
"span": {
"replace": [
{
"start": [
2,
5
],
"end": [
2,
11
]
},
{
"start": [
2,
5
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the 'string' identifier with the 'int' identifier"
},
{
"span": {
"replace": [
{
"start": [
3,
6
],
"end": [
3,
8
]
},
{
"start": [
3,
6
],
"end": [
3,
8
]
}
]
},
"summary": "Replaced the 'p1' identifier with the 'p3' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"pointer-types.go"
],
"patch": [
"diff --git a/pointer-types.go b/pointer-types.go",
"index 74ff673..95e685d 100644",
"--- a/pointer-types.go",
"+++ b/pointer-types.go",
"@@ -1,6 +1,6 @@",
" type (",
"-p1 *string",
"-p2 **p1",
"+p1 *int",
"+p2 **p3",
" )",
" type (",
" p1 *string"
],
"gitDir": "test/corpus/repos/go",
"shas": "2f99a01b337c02263ca4e9399902b16aaba1dedf..f13af84d4486664581e87d4a034aef0bad3a207a"
}
,{
"testCaseDescription": "go-pointer-types-delete-replacement-test",
"expectedResult": {
"changes": {
"pointer-types.go": [
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
3
]
}
},
"summary": "Deleted the 'p1' identifier"
},
{
"span": {
"delete": {
"start": [
2,
5
],
"end": [
2,
8
]
}
},
"summary": "Deleted the 'int' identifier"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
3
]
}
},
"summary": "Deleted the 'p2' identifier"
},
{
"span": {
"delete": {
"start": [
3,
6
],
"end": [
3,
8
]
}
},
"summary": "Deleted the 'p3' identifier"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
6,
3
]
}
},
"summary": "Deleted the 'p1' identifier"
},
{
"span": {
"delete": {
"start": [
6,
5
],
"end": [
6,
11
]
}
},
"summary": "Deleted the 'string' identifier"
},
{
"span": {
"delete": {
"start": [
7,
1
],
"end": [
7,
3
]
}
},
"summary": "Deleted the 'p2' identifier"
},
{
"span": {
"delete": {
"start": [
7,
6
],
"end": [
7,
8
]
}
},
"summary": "Deleted the 'p1' identifier"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
3
]
}
},
"summary": "Added the 'p1' identifier"
},
{
"span": {
"insert": {
"start": [
6,
5
],
"end": [
6,
8
]
}
},
"summary": "Added the 'int' identifier"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
7,
3
]
}
},
"summary": "Added the 'p2' identifier"
},
{
"span": {
"insert": {
"start": [
7,
6
],
"end": [
7,
8
]
}
},
"summary": "Added the 'p3' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"pointer-types.go"
],
"patch": [
"diff --git a/pointer-types.go b/pointer-types.go",
"index 95e685d..4556eeb 100644",
"--- a/pointer-types.go",
"+++ b/pointer-types.go",
"@@ -1,12 +1,8 @@",
" type (",
"-p1 *int",
"-p2 **p3",
"-)",
"-type (",
" p1 *string",
" p2 **p1",
" )",
" type (",
"-p1 *string",
"-p2 **p1",
"+p1 *int",
"+p2 **p3",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "f13af84d4486664581e87d4a034aef0bad3a207a..1dfbf23712676794ded97d5e9a411ce7ce56fc17"
}
,{
"testCaseDescription": "go-pointer-types-delete-test",
"expectedResult": {
"changes": {
"pointer-types.go": [
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
3
]
}
},
"summary": "Deleted the 'p1' identifier"
},
{
"span": {
"delete": {
"start": [
2,
5
],
"end": [
2,
11
]
}
},
"summary": "Deleted the 'string' identifier"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
3
]
}
},
"summary": "Deleted the 'p2' identifier"
},
{
"span": {
"delete": {
"start": [
3,
6
],
"end": [
3,
8
]
}
},
"summary": "Deleted the 'p1' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"pointer-types.go"
],
"patch": [
"diff --git a/pointer-types.go b/pointer-types.go",
"index 4556eeb..5d13f48 100644",
"--- a/pointer-types.go",
"+++ b/pointer-types.go",
"@@ -1,8 +1,4 @@",
" type (",
"-p1 *string",
"-p2 **p1",
"-)",
"-type (",
" p1 *int",
" p2 **p3",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "1dfbf23712676794ded97d5e9a411ce7ce56fc17..d8ac0c302b514259999149901eb3c217040e7407"
}
,{
"testCaseDescription": "go-pointer-types-delete-rest-test",
"expectedResult": {
"changes": {
"pointer-types.go": [
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
3
]
}
},
"summary": "Deleted the 'p1' identifier"
},
{
"span": {
"delete": {
"start": [
2,
5
],
"end": [
2,
8
]
}
},
"summary": "Deleted the 'int' identifier"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
3
]
}
},
"summary": "Deleted the 'p2' identifier"
},
{
"span": {
"delete": {
"start": [
3,
6
],
"end": [
3,
8
]
}
},
"summary": "Deleted the 'p3' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"pointer-types.go"
],
"patch": [
"diff --git a/pointer-types.go b/pointer-types.go",
"index 5d13f48..e69de29 100644",
"--- a/pointer-types.go",
"+++ b/pointer-types.go",
"@@ -1,4 +0,0 @@",
"-type (",
"-p1 *int",
"-p2 **p3",
"-)"
],
"gitDir": "test/corpus/repos/go",
"shas": "d8ac0c302b514259999149901eb3c217040e7407..043e40fb43f738d1d0ddd89c38bc83159bcc7a8f"
}]

View File

@ -0,0 +1,695 @@
[{
"testCaseDescription": "go-qualified-types-insert-test",
"expectedResult": {
"changes": {
"qualified-types.go": [
{
"span": {
"insert": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Added the 'b' identifier"
},
{
"span": {
"insert": {
"start": [
1,
10
],
"end": [
1,
11
]
}
},
"summary": "Added the 'c' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"qualified-types.go"
],
"patch": [
"diff --git a/qualified-types.go b/qualified-types.go",
"index e69de29..7840cac 100644",
"--- a/qualified-types.go",
"+++ b/qualified-types.go",
"@@ -0,0 +1 @@",
"+type a b.c"
],
"gitDir": "test/corpus/repos/go",
"shas": "a5b8a6804181af3a1387f9a23e3f85c44ddb6082..1534853219b560e38a40a23b1f54b3791e78a6a8"
}
,{
"testCaseDescription": "go-qualified-types-replacement-insert-test",
"expectedResult": {
"changes": {
"qualified-types.go": [
{
"span": {
"insert": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Added the 'x' identifier"
},
{
"span": {
"insert": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Added the 'y' identifier"
},
{
"span": {
"insert": {
"start": [
1,
10
],
"end": [
1,
11
]
}
},
"summary": "Added the 'z' identifier"
},
{
"span": {
"insert": {
"start": [
2,
6
],
"end": [
2,
7
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
2,
8
],
"end": [
2,
9
]
}
},
"summary": "Added the 'b' identifier"
},
{
"span": {
"insert": {
"start": [
2,
10
],
"end": [
2,
11
]
}
},
"summary": "Added the 'c' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"qualified-types.go"
],
"patch": [
"diff --git a/qualified-types.go b/qualified-types.go",
"index 7840cac..0256b29 100644",
"--- a/qualified-types.go",
"+++ b/qualified-types.go",
"@@ -1 +1,3 @@",
"+type x y.z",
"+type a b.c",
" type a b.c"
],
"gitDir": "test/corpus/repos/go",
"shas": "1534853219b560e38a40a23b1f54b3791e78a6a8..9a0469bb91c527b8c2d07f8ec53ab8cdfcf7bd9f"
}
,{
"testCaseDescription": "go-qualified-types-delete-insert-test",
"expectedResult": {
"changes": {
"qualified-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
7
]
},
{
"start": [
1,
6
],
"end": [
1,
7
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'a' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
8
],
"end": [
1,
9
]
},
{
"start": [
1,
8
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'y' identifier with the 'b' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
10
],
"end": [
1,
11
]
},
{
"start": [
1,
10
],
"end": [
1,
11
]
}
]
},
"summary": "Replaced the 'z' identifier with the 'c' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"qualified-types.go"
],
"patch": [
"diff --git a/qualified-types.go b/qualified-types.go",
"index 0256b29..e963dfd 100644",
"--- a/qualified-types.go",
"+++ b/qualified-types.go",
"@@ -1,3 +1,3 @@",
"-type x y.z",
"+type a b.c",
" type a b.c",
" type a b.c"
],
"gitDir": "test/corpus/repos/go",
"shas": "9a0469bb91c527b8c2d07f8ec53ab8cdfcf7bd9f..da94ab3ccc5de8e4a034254dbe2909d2b8fa9626"
}
,{
"testCaseDescription": "go-qualified-types-replacement-test",
"expectedResult": {
"changes": {
"qualified-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
7
]
},
{
"start": [
1,
6
],
"end": [
1,
7
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'x' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
8
],
"end": [
1,
9
]
},
{
"start": [
1,
8
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'y' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
10
],
"end": [
1,
11
]
},
{
"start": [
1,
10
],
"end": [
1,
11
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'z' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"qualified-types.go"
],
"patch": [
"diff --git a/qualified-types.go b/qualified-types.go",
"index e963dfd..0256b29 100644",
"--- a/qualified-types.go",
"+++ b/qualified-types.go",
"@@ -1,3 +1,3 @@",
"-type a b.c",
"+type x y.z",
" type a b.c",
" type a b.c"
],
"gitDir": "test/corpus/repos/go",
"shas": "da94ab3ccc5de8e4a034254dbe2909d2b8fa9626..d75d90717c183e1beaefacd4e4531d6d7da64316"
}
,{
"testCaseDescription": "go-qualified-types-delete-replacement-test",
"expectedResult": {
"changes": {
"qualified-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'x' identifier"
},
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Deleted the 'y' identifier"
},
{
"span": {
"delete": {
"start": [
1,
10
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'z' identifier"
},
{
"span": {
"delete": {
"start": [
2,
6
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
2,
8
],
"end": [
2,
9
]
}
},
"summary": "Deleted the 'b' identifier"
},
{
"span": {
"delete": {
"start": [
2,
10
],
"end": [
2,
11
]
}
},
"summary": "Deleted the 'c' identifier"
},
{
"span": {
"insert": {
"start": [
2,
6
],
"end": [
2,
7
]
}
},
"summary": "Added the 'x' identifier"
},
{
"span": {
"insert": {
"start": [
2,
8
],
"end": [
2,
9
]
}
},
"summary": "Added the 'y' identifier"
},
{
"span": {
"insert": {
"start": [
2,
10
],
"end": [
2,
11
]
}
},
"summary": "Added the 'z' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"qualified-types.go"
],
"patch": [
"diff --git a/qualified-types.go b/qualified-types.go",
"index 0256b29..4525e0a 100644",
"--- a/qualified-types.go",
"+++ b/qualified-types.go",
"@@ -1,3 +1,2 @@",
"-type x y.z",
"-type a b.c",
" type a b.c",
"+type x y.z"
],
"gitDir": "test/corpus/repos/go",
"shas": "d75d90717c183e1beaefacd4e4531d6d7da64316..40fe32e2e038391f91cb6a8e14ac554e222e1465"
}
,{
"testCaseDescription": "go-qualified-types-delete-test",
"expectedResult": {
"changes": {
"qualified-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Deleted the 'b' identifier"
},
{
"span": {
"delete": {
"start": [
1,
10
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'c' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"qualified-types.go"
],
"patch": [
"diff --git a/qualified-types.go b/qualified-types.go",
"index 4525e0a..f31a963 100644",
"--- a/qualified-types.go",
"+++ b/qualified-types.go",
"@@ -1,2 +1 @@",
"-type a b.c",
" type x y.z"
],
"gitDir": "test/corpus/repos/go",
"shas": "40fe32e2e038391f91cb6a8e14ac554e222e1465..3cd11bed0abcaeb3d4ce762dc40ef452183e6768"
}
,{
"testCaseDescription": "go-qualified-types-delete-rest-test",
"expectedResult": {
"changes": {
"qualified-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'x' identifier"
},
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Deleted the 'y' identifier"
},
{
"span": {
"delete": {
"start": [
1,
10
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'z' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"qualified-types.go"
],
"patch": [
"diff --git a/qualified-types.go b/qualified-types.go",
"index f31a963..e69de29 100644",
"--- a/qualified-types.go",
"+++ b/qualified-types.go",
"@@ -1 +0,0 @@",
"-type x y.z"
],
"gitDir": "test/corpus/repos/go",
"shas": "3cd11bed0abcaeb3d4ce762dc40ef452183e6768..4605c9308ffc84f9d63dc5e62562b0461d53d5b9"
}]

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,547 @@
[{
"testCaseDescription": "go-select-statements-insert-test",
"expectedResult": {
"changes": {
"select-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
10,
2
]
}
},
"summary": "Added a select statement"
}
]
},
"errors": {}
},
"filePaths": [
"select-statements.go"
],
"patch": [
"diff --git a/select-statements.go b/select-statements.go",
"index e69de29..7fe1c0b 100644",
"--- a/select-statements.go",
"+++ b/select-statements.go",
"@@ -0,0 +1,10 @@",
"+select {",
"+ case x := <-c:",
"+ println(x)",
"+ case y <- c:",
"+ println(5)",
"+ case <-time.After(1):",
"+ println(6)",
"+ default:",
"+ return",
"+}"
],
"gitDir": "test/corpus/repos/go",
"shas": "c02f9252b66f4d334e7e4d5cc2b56665c5d0b45f..2b2fbf697988912a16c858851710652dae25a559"
}
,{
"testCaseDescription": "go-select-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"select-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
10,
2
]
}
},
"summary": "Added a select statement"
},
{
"span": {
"insert": {
"start": [
11,
1
],
"end": [
20,
2
]
}
},
"summary": "Added a select statement"
}
]
},
"errors": {}
},
"filePaths": [
"select-statements.go"
],
"patch": [
"diff --git a/select-statements.go b/select-statements.go",
"index 7fe1c0b..1403fc7 100644",
"--- a/select-statements.go",
"+++ b/select-statements.go",
"@@ -1,4 +1,24 @@",
" select {",
"+ case a := <-c:",
"+ println(x)",
"+ case b <- c:",
"+ println(5)",
"+ case <-time.After(2):",
"+ println(6)",
"+ default:",
"+ return",
"+}",
"+select {",
"+ case x := <-c:",
"+ println(x)",
"+ case y <- c:",
"+ println(5)",
"+ case <-time.After(1):",
"+ println(6)",
"+ default:",
"+ return",
"+}",
"+select {",
" case x := <-c:",
" println(x)",
" case y <- c:"
],
"gitDir": "test/corpus/repos/go",
"shas": "2b2fbf697988912a16c858851710652dae25a559..983b410af87ea7510331b9acfece407fa4388e09"
}
,{
"testCaseDescription": "go-select-statements-delete-insert-test",
"expectedResult": {
"changes": {
"select-statements.go": [
{
"span": {
"replace": [
{
"start": [
2,
8
],
"end": [
2,
9
]
},
{
"start": [
2,
8
],
"end": [
2,
9
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'x' identifier"
},
{
"span": {
"replace": [
{
"start": [
4,
8
],
"end": [
4,
9
]
},
{
"start": [
4,
8
],
"end": [
4,
9
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'y' identifier"
},
{
"span": {
"replace": [
{
"start": [
6,
21
],
"end": [
6,
22
]
},
{
"start": [
6,
21
],
"end": [
6,
22
]
}
]
},
"summary": "Replaced '2' with '1'"
}
]
},
"errors": {}
},
"filePaths": [
"select-statements.go"
],
"patch": [
"diff --git a/select-statements.go b/select-statements.go",
"index 1403fc7..3e83983 100644",
"--- a/select-statements.go",
"+++ b/select-statements.go",
"@@ -1,9 +1,9 @@",
" select {",
"- case a := <-c:",
"+ case x := <-c:",
" println(x)",
"- case b <- c:",
"+ case y <- c:",
" println(5)",
"- case <-time.After(2):",
"+ case <-time.After(1):",
" println(6)",
" default:",
" return"
],
"gitDir": "test/corpus/repos/go",
"shas": "983b410af87ea7510331b9acfece407fa4388e09..a23994405fb8e283ccb2d2c95074563cceb23b83"
}
,{
"testCaseDescription": "go-select-statements-replacement-test",
"expectedResult": {
"changes": {
"select-statements.go": [
{
"span": {
"replace": [
{
"start": [
2,
8
],
"end": [
2,
9
]
},
{
"start": [
2,
8
],
"end": [
2,
9
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'a' identifier"
},
{
"span": {
"replace": [
{
"start": [
4,
8
],
"end": [
4,
9
]
},
{
"start": [
4,
8
],
"end": [
4,
9
]
}
]
},
"summary": "Replaced the 'y' identifier with the 'b' identifier"
},
{
"span": {
"replace": [
{
"start": [
6,
21
],
"end": [
6,
22
]
},
{
"start": [
6,
21
],
"end": [
6,
22
]
}
]
},
"summary": "Replaced '1' with '2'"
}
]
},
"errors": {}
},
"filePaths": [
"select-statements.go"
],
"patch": [
"diff --git a/select-statements.go b/select-statements.go",
"index 3e83983..1403fc7 100644",
"--- a/select-statements.go",
"+++ b/select-statements.go",
"@@ -1,9 +1,9 @@",
" select {",
"- case x := <-c:",
"+ case a := <-c:",
" println(x)",
"- case y <- c:",
"+ case b <- c:",
" println(5)",
"- case <-time.After(1):",
"+ case <-time.After(2):",
" println(6)",
" default:",
" return"
],
"gitDir": "test/corpus/repos/go",
"shas": "a23994405fb8e283ccb2d2c95074563cceb23b83..3f72a17c112bb126b288f9683109d13f918567e6"
}
,{
"testCaseDescription": "go-select-statements-delete-replacement-test",
"expectedResult": {
"changes": {
"select-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
10,
2
]
}
},
"summary": "Deleted a select statement"
},
{
"span": {
"delete": {
"start": [
11,
1
],
"end": [
20,
2
]
}
},
"summary": "Deleted a select statement"
},
{
"span": {
"insert": {
"start": [
11,
1
],
"end": [
20,
2
]
}
},
"summary": "Added a select statement"
}
]
},
"errors": {}
},
"filePaths": [
"select-statements.go"
],
"patch": [
"diff --git a/select-statements.go b/select-statements.go",
"index 1403fc7..234dd89 100644",
"--- a/select-statements.go",
"+++ b/select-statements.go",
"@@ -1,14 +1,4 @@",
" select {",
"- case a := <-c:",
"- println(x)",
"- case b <- c:",
"- println(5)",
"- case <-time.After(2):",
"- println(6)",
"- default:",
"- return",
"-}",
"-select {",
" case x := <-c:",
" println(x)",
" case y <- c:",
"@@ -19,11 +9,11 @@ select {",
" return",
" }",
" select {",
"- case x := <-c:",
"+ case a := <-c:",
" println(x)",
"- case y <- c:",
"+ case b <- c:",
" println(5)",
"- case <-time.After(1):",
"+ case <-time.After(2):",
" println(6)",
" default:",
" return"
],
"gitDir": "test/corpus/repos/go",
"shas": "3f72a17c112bb126b288f9683109d13f918567e6..9d5bc8c2e6e70762403f8a1f02ac863410533023"
}
,{
"testCaseDescription": "go-select-statements-delete-test",
"expectedResult": {
"changes": {
"select-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
10,
2
]
}
},
"summary": "Deleted a select statement"
}
]
},
"errors": {}
},
"filePaths": [
"select-statements.go"
],
"patch": [
"diff --git a/select-statements.go b/select-statements.go",
"index 234dd89..d513030 100644",
"--- a/select-statements.go",
"+++ b/select-statements.go",
"@@ -1,14 +1,4 @@",
" select {",
"- case x := <-c:",
"- println(x)",
"- case y <- c:",
"- println(5)",
"- case <-time.After(1):",
"- println(6)",
"- default:",
"- return",
"-}",
"-select {",
" case a := <-c:",
" println(x)",
" case b <- c:"
],
"gitDir": "test/corpus/repos/go",
"shas": "9d5bc8c2e6e70762403f8a1f02ac863410533023..30985a629ade98c4fde5bf79a200bd2697dc9d9f"
}
,{
"testCaseDescription": "go-select-statements-delete-rest-test",
"expectedResult": {
"changes": {
"select-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
10,
2
]
}
},
"summary": "Deleted a select statement"
}
]
},
"errors": {}
},
"filePaths": [
"select-statements.go"
],
"patch": [
"diff --git a/select-statements.go b/select-statements.go",
"index d513030..e69de29 100644",
"--- a/select-statements.go",
"+++ b/select-statements.go",
"@@ -1,10 +0,0 @@",
"-select {",
"- case a := <-c:",
"- println(x)",
"- case b <- c:",
"- println(5)",
"- case <-time.After(2):",
"- println(6)",
"- default:",
"- return",
"-}"
],
"gitDir": "test/corpus/repos/go",
"shas": "30985a629ade98c4fde5bf79a200bd2697dc9d9f..201c2f06d17d14e12c9861e2a94372fc41441178"
}]

View File

@ -0,0 +1,455 @@
[{
"testCaseDescription": "go-selector-expressions-insert-test",
"expectedResult": {
"changes": {
"selector-expressions.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Added the 'a[b][c]()' function call"
}
]
},
"errors": {}
},
"filePaths": [
"selector-expressions.go"
],
"patch": [
"diff --git a/selector-expressions.go b/selector-expressions.go",
"index e69de29..7be43f2 100644",
"--- a/selector-expressions.go",
"+++ b/selector-expressions.go",
"@@ -0,0 +1 @@",
"+a.b.c()"
],
"gitDir": "test/corpus/repos/go",
"shas": "b8520b47d7e23a8b805613ba5e28d123748a7e86..53e9575bb4a95b6a13a9289b3cb198389c3c5018"
}
,{
"testCaseDescription": "go-selector-expressions-replacement-insert-test",
"expectedResult": {
"changes": {
"selector-expressions.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Added the 'x[y][z]()' function call"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
8
]
}
},
"summary": "Added the 'a[b][c]()' function call"
}
]
},
"errors": {}
},
"filePaths": [
"selector-expressions.go"
],
"patch": [
"diff --git a/selector-expressions.go b/selector-expressions.go",
"index 7be43f2..4fa8605 100644",
"--- a/selector-expressions.go",
"+++ b/selector-expressions.go",
"@@ -1 +1,3 @@",
"+x.y.z()",
"+a.b.c()",
" a.b.c()"
],
"gitDir": "test/corpus/repos/go",
"shas": "53e9575bb4a95b6a13a9289b3cb198389c3c5018..05337c7344ffd11906be9b6603043c1bcf0f7dff"
}
,{
"testCaseDescription": "go-selector-expressions-delete-insert-test",
"expectedResult": {
"changes": {
"selector-expressions.go": [
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
2
]
},
{
"start": [
1,
1
],
"end": [
1,
2
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'a' identifier in the a[b] subscript access"
},
{
"span": {
"replace": [
{
"start": [
1,
3
],
"end": [
1,
4
]
},
{
"start": [
1,
3
],
"end": [
1,
4
]
}
]
},
"summary": "Replaced the 'y' identifier with the 'b' identifier in the a[b] subscript access"
},
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
6
]
},
{
"start": [
1,
5
],
"end": [
1,
6
]
}
]
},
"summary": "Replaced the 'z' identifier with the 'c' identifier in the a[b][c] subscript access"
}
]
},
"errors": {}
},
"filePaths": [
"selector-expressions.go"
],
"patch": [
"diff --git a/selector-expressions.go b/selector-expressions.go",
"index 4fa8605..2a586da 100644",
"--- a/selector-expressions.go",
"+++ b/selector-expressions.go",
"@@ -1,3 +1,3 @@",
"-x.y.z()",
"+a.b.c()",
" a.b.c()",
" a.b.c()"
],
"gitDir": "test/corpus/repos/go",
"shas": "05337c7344ffd11906be9b6603043c1bcf0f7dff..4bcafdd401ffbfb0e29802793ed59f20908986a6"
}
,{
"testCaseDescription": "go-selector-expressions-replacement-test",
"expectedResult": {
"changes": {
"selector-expressions.go": [
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
2
]
},
{
"start": [
1,
1
],
"end": [
1,
2
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'x' identifier in the x[y] subscript access"
},
{
"span": {
"replace": [
{
"start": [
1,
3
],
"end": [
1,
4
]
},
{
"start": [
1,
3
],
"end": [
1,
4
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'y' identifier in the x[y] subscript access"
},
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
6
]
},
{
"start": [
1,
5
],
"end": [
1,
6
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'z' identifier in the x[y][z] subscript access"
}
]
},
"errors": {}
},
"filePaths": [
"selector-expressions.go"
],
"patch": [
"diff --git a/selector-expressions.go b/selector-expressions.go",
"index 2a586da..4fa8605 100644",
"--- a/selector-expressions.go",
"+++ b/selector-expressions.go",
"@@ -1,3 +1,3 @@",
"-a.b.c()",
"+x.y.z()",
" a.b.c()",
" a.b.c()"
],
"gitDir": "test/corpus/repos/go",
"shas": "4bcafdd401ffbfb0e29802793ed59f20908986a6..1763e869f9b7050dc5703f293808233c46910062"
}
,{
"testCaseDescription": "go-selector-expressions-delete-replacement-test",
"expectedResult": {
"changes": {
"selector-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'x[y][z]()' function call"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
8
]
}
},
"summary": "Deleted the 'a[b][c]()' function call"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
8
]
}
},
"summary": "Added the 'x[y][z]()' function call"
}
]
},
"errors": {}
},
"filePaths": [
"selector-expressions.go"
],
"patch": [
"diff --git a/selector-expressions.go b/selector-expressions.go",
"index 4fa8605..3e2d0bd 100644",
"--- a/selector-expressions.go",
"+++ b/selector-expressions.go",
"@@ -1,3 +1,2 @@",
"-x.y.z()",
"-a.b.c()",
" a.b.c()",
"+x.y.z()"
],
"gitDir": "test/corpus/repos/go",
"shas": "1763e869f9b7050dc5703f293808233c46910062..562bbf82089ed1bc7d77c4698451746939455f51"
}
,{
"testCaseDescription": "go-selector-expressions-delete-test",
"expectedResult": {
"changes": {
"selector-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'a[b][c]()' function call"
}
]
},
"errors": {}
},
"filePaths": [
"selector-expressions.go"
],
"patch": [
"diff --git a/selector-expressions.go b/selector-expressions.go",
"index 3e2d0bd..00b9e7c 100644",
"--- a/selector-expressions.go",
"+++ b/selector-expressions.go",
"@@ -1,2 +1 @@",
"-a.b.c()",
" x.y.z()"
],
"gitDir": "test/corpus/repos/go",
"shas": "562bbf82089ed1bc7d77c4698451746939455f51..3ea379fb7d49d67e17b2bd53b58af0298c055ccc"
}
,{
"testCaseDescription": "go-selector-expressions-delete-rest-test",
"expectedResult": {
"changes": {
"selector-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'x[y][z]()' function call"
}
]
},
"errors": {}
},
"filePaths": [
"selector-expressions.go"
],
"patch": [
"diff --git a/selector-expressions.go b/selector-expressions.go",
"index 00b9e7c..e69de29 100644",
"--- a/selector-expressions.go",
"+++ b/selector-expressions.go",
"@@ -1 +0,0 @@",
"-x.y.z()"
],
"gitDir": "test/corpus/repos/go",
"shas": "3ea379fb7d49d67e17b2bd53b58af0298c055ccc..bef4b21e0fe9824b79e8b12bfa32867c8a4433a7"
}]

View File

@ -0,0 +1,521 @@
[{
"testCaseDescription": "go-send-statements-insert-test",
"expectedResult": {
"changes": {
"send-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Added 'foo' identifier"
},
{
"span": {
"insert": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Added '5'"
}
]
},
"errors": {}
},
"filePaths": [
"send-statements.go"
],
"patch": [
"diff --git a/send-statements.go b/send-statements.go",
"index e69de29..9df974c 100644",
"--- a/send-statements.go",
"+++ b/send-statements.go",
"@@ -0,0 +1 @@",
"+foo <- 5"
],
"gitDir": "test/corpus/repos/go",
"shas": "7fd6dea031e26a02c1743a205dc1489a7e050468..0c3bf2eda05dc415465ee2ed1bfe6ac87a0d41bd"
}
,{
"testCaseDescription": "go-send-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"send-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Added 'bar' identifier"
},
{
"span": {
"insert": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Added '6'"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
4
]
}
},
"summary": "Added 'foo' identifier"
},
{
"span": {
"insert": {
"start": [
2,
8
],
"end": [
2,
9
]
}
},
"summary": "Added '5'"
}
]
},
"errors": {}
},
"filePaths": [
"send-statements.go"
],
"patch": [
"diff --git a/send-statements.go b/send-statements.go",
"index 9df974c..de76cee 100644",
"--- a/send-statements.go",
"+++ b/send-statements.go",
"@@ -1 +1,3 @@",
"+bar <- 6",
"+foo <- 5",
" foo <- 5"
],
"gitDir": "test/corpus/repos/go",
"shas": "0c3bf2eda05dc415465ee2ed1bfe6ac87a0d41bd..abab5451f999eab126c0ad6f1312d732537d1685"
}
,{
"testCaseDescription": "go-send-statements-delete-insert-test",
"expectedResult": {
"changes": {
"send-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
4
]
},
{
"start": [
1,
1
],
"end": [
1,
4
]
}
]
},
"summary": "Replaced the 'bar' identifier with the 'foo' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
8
],
"end": [
1,
9
]
},
{
"start": [
1,
8
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced '6' with '5'"
}
]
},
"errors": {}
},
"filePaths": [
"send-statements.go"
],
"patch": [
"diff --git a/send-statements.go b/send-statements.go",
"index de76cee..d487575 100644",
"--- a/send-statements.go",
"+++ b/send-statements.go",
"@@ -1,3 +1,3 @@",
"-bar <- 6",
"+foo <- 5",
" foo <- 5",
" foo <- 5"
],
"gitDir": "test/corpus/repos/go",
"shas": "abab5451f999eab126c0ad6f1312d732537d1685..b88435c07e6bcc26a890ef52e2cc3a63b4ad2155"
}
,{
"testCaseDescription": "go-send-statements-replacement-test",
"expectedResult": {
"changes": {
"send-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
4
]
},
{
"start": [
1,
1
],
"end": [
1,
4
]
}
]
},
"summary": "Replaced the 'foo' identifier with the 'bar' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
8
],
"end": [
1,
9
]
},
{
"start": [
1,
8
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced '5' with '6'"
}
]
},
"errors": {}
},
"filePaths": [
"send-statements.go"
],
"patch": [
"diff --git a/send-statements.go b/send-statements.go",
"index d487575..de76cee 100644",
"--- a/send-statements.go",
"+++ b/send-statements.go",
"@@ -1,3 +1,3 @@",
"-foo <- 5",
"+bar <- 6",
" foo <- 5",
" foo <- 5"
],
"gitDir": "test/corpus/repos/go",
"shas": "b88435c07e6bcc26a890ef52e2cc3a63b4ad2155..956a353953bd55204b2eb37fdc8727198208edc8"
}
,{
"testCaseDescription": "go-send-statements-delete-replacement-test",
"expectedResult": {
"changes": {
"send-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Deleted 'bar' identifier"
},
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Deleted '6'"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
4
]
}
},
"summary": "Deleted 'foo' identifier"
},
{
"span": {
"delete": {
"start": [
2,
8
],
"end": [
2,
9
]
}
},
"summary": "Deleted '5'"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
4
]
}
},
"summary": "Added 'bar' identifier"
},
{
"span": {
"insert": {
"start": [
2,
8
],
"end": [
2,
9
]
}
},
"summary": "Added '6'"
}
]
},
"errors": {}
},
"filePaths": [
"send-statements.go"
],
"patch": [
"diff --git a/send-statements.go b/send-statements.go",
"index de76cee..65a1c23 100644",
"--- a/send-statements.go",
"+++ b/send-statements.go",
"@@ -1,3 +1,2 @@",
"-bar <- 6",
"-foo <- 5",
" foo <- 5",
"+bar <- 6"
],
"gitDir": "test/corpus/repos/go",
"shas": "956a353953bd55204b2eb37fdc8727198208edc8..6640556f9db698688695109406ffbdb65d89e298"
}
,{
"testCaseDescription": "go-send-statements-delete-test",
"expectedResult": {
"changes": {
"send-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Deleted 'foo' identifier"
},
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Deleted '5'"
}
]
},
"errors": {}
},
"filePaths": [
"send-statements.go"
],
"patch": [
"diff --git a/send-statements.go b/send-statements.go",
"index 65a1c23..bab29cb 100644",
"--- a/send-statements.go",
"+++ b/send-statements.go",
"@@ -1,2 +1 @@",
"-foo <- 5",
" bar <- 6"
],
"gitDir": "test/corpus/repos/go",
"shas": "6640556f9db698688695109406ffbdb65d89e298..bd1886ba3d3f3e1fde4b18c020b346d71883ee9e"
}
,{
"testCaseDescription": "go-send-statements-delete-rest-test",
"expectedResult": {
"changes": {
"send-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Deleted 'bar' identifier"
},
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Deleted '6'"
}
]
},
"errors": {}
},
"filePaths": [
"send-statements.go"
],
"patch": [
"diff --git a/send-statements.go b/send-statements.go",
"index bab29cb..e69de29 100644",
"--- a/send-statements.go",
"+++ b/send-statements.go",
"@@ -1 +0,0 @@",
"-bar <- 6"
],
"gitDir": "test/corpus/repos/go",
"shas": "bd1886ba3d3f3e1fde4b18c020b346d71883ee9e..927f995f9a27002e1694b5d3ce66a7dbbfda6720"
}]

View File

@ -0,0 +1,629 @@
[{
"testCaseDescription": "go-short-var-declarations-insert-test",
"expectedResult": {
"changes": {
"short-var-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"short-var-declarations.go"
],
"patch": [
"diff --git a/short-var-declarations.go b/short-var-declarations.go",
"index e69de29..99b7041 100644",
"--- a/short-var-declarations.go",
"+++ b/short-var-declarations.go",
"@@ -0,0 +1 @@",
"+a, b := 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "d77b70cb3981afaf807f3e56652ecd386101cb2b..923c4c5fcf1002927a78d428eefab190c7e2c730"
}
,{
"testCaseDescription": "go-short-var-declarations-replacement-insert-test",
"expectedResult": {
"changes": {
"short-var-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'x' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'y' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Added the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"short-var-declarations.go"
],
"patch": [
"diff --git a/short-var-declarations.go b/short-var-declarations.go",
"index 99b7041..220aab8 100644",
"--- a/short-var-declarations.go",
"+++ b/short-var-declarations.go",
"@@ -1 +1,3 @@",
"+x, y := 3, 4",
"+a, b := 1, 2",
" a, b := 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "923c4c5fcf1002927a78d428eefab190c7e2c730..62e0fff2590e53bca217d3b3fb46c7f6f86822c1"
}
,{
"testCaseDescription": "go-short-var-declarations-delete-insert-test",
"expectedResult": {
"changes": {
"short-var-declarations.go": [
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
2
]
},
{
"start": [
1,
1
],
"end": [
1,
2
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'a' identifier in the a variable"
},
{
"span": {
"replace": [
{
"start": [
1,
9
],
"end": [
1,
10
]
},
{
"start": [
1,
9
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced '3' with '1' in the a variable"
},
{
"span": {
"replace": [
{
"start": [
1,
4
],
"end": [
1,
5
]
},
{
"start": [
1,
4
],
"end": [
1,
5
]
}
]
},
"summary": "Replaced the 'y' identifier with the 'b' identifier in the b variable"
},
{
"span": {
"replace": [
{
"start": [
1,
12
],
"end": [
1,
13
]
},
{
"start": [
1,
12
],
"end": [
1,
13
]
}
]
},
"summary": "Replaced '4' with '2' in the b variable"
}
]
},
"errors": {}
},
"filePaths": [
"short-var-declarations.go"
],
"patch": [
"diff --git a/short-var-declarations.go b/short-var-declarations.go",
"index 220aab8..96ba966 100644",
"--- a/short-var-declarations.go",
"+++ b/short-var-declarations.go",
"@@ -1,3 +1,3 @@",
"-x, y := 3, 4",
"+a, b := 1, 2",
" a, b := 1, 2",
" a, b := 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "62e0fff2590e53bca217d3b3fb46c7f6f86822c1..ca28a3beeb3b19e152ad702d5c8ba7d4abcb87e2"
}
,{
"testCaseDescription": "go-short-var-declarations-replacement-test",
"expectedResult": {
"changes": {
"short-var-declarations.go": [
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
2
]
},
{
"start": [
1,
1
],
"end": [
1,
2
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'x' identifier in the x variable"
},
{
"span": {
"replace": [
{
"start": [
1,
9
],
"end": [
1,
10
]
},
{
"start": [
1,
9
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced '1' with '3' in the x variable"
},
{
"span": {
"replace": [
{
"start": [
1,
4
],
"end": [
1,
5
]
},
{
"start": [
1,
4
],
"end": [
1,
5
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'y' identifier in the y variable"
},
{
"span": {
"replace": [
{
"start": [
1,
12
],
"end": [
1,
13
]
},
{
"start": [
1,
12
],
"end": [
1,
13
]
}
]
},
"summary": "Replaced '2' with '4' in the y variable"
}
]
},
"errors": {}
},
"filePaths": [
"short-var-declarations.go"
],
"patch": [
"diff --git a/short-var-declarations.go b/short-var-declarations.go",
"index 96ba966..220aab8 100644",
"--- a/short-var-declarations.go",
"+++ b/short-var-declarations.go",
"@@ -1,3 +1,3 @@",
"-a, b := 1, 2",
"+x, y := 3, 4",
" a, b := 1, 2",
" a, b := 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "ca28a3beeb3b19e152ad702d5c8ba7d4abcb87e2..601d4dd43130450c08e7e7b34bc3b35cd6df83cc"
}
,{
"testCaseDescription": "go-short-var-declarations-delete-replacement-test",
"expectedResult": {
"changes": {
"short-var-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'x' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'y' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Added the 'x' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Added the 'y' variable"
}
]
},
"errors": {}
},
"filePaths": [
"short-var-declarations.go"
],
"patch": [
"diff --git a/short-var-declarations.go b/short-var-declarations.go",
"index 220aab8..53cb4ed 100644",
"--- a/short-var-declarations.go",
"+++ b/short-var-declarations.go",
"@@ -1,3 +1,2 @@",
"-x, y := 3, 4",
"-a, b := 1, 2",
" a, b := 1, 2",
"+x, y := 3, 4"
],
"gitDir": "test/corpus/repos/go",
"shas": "601d4dd43130450c08e7e7b34bc3b35cd6df83cc..b494ce9f37460cdcc5f62dbf78571c0e1134ce60"
}
,{
"testCaseDescription": "go-short-var-declarations-delete-test",
"expectedResult": {
"changes": {
"short-var-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"short-var-declarations.go"
],
"patch": [
"diff --git a/short-var-declarations.go b/short-var-declarations.go",
"index 53cb4ed..9209ec7 100644",
"--- a/short-var-declarations.go",
"+++ b/short-var-declarations.go",
"@@ -1,2 +1 @@",
"-a, b := 1, 2",
" x, y := 3, 4"
],
"gitDir": "test/corpus/repos/go",
"shas": "b494ce9f37460cdcc5f62dbf78571c0e1134ce60..6943eb4765b07143acf4bead143f4e9927d67e74"
}
,{
"testCaseDescription": "go-short-var-declarations-delete-rest-test",
"expectedResult": {
"changes": {
"short-var-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'x' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'y' variable"
}
]
},
"errors": {}
},
"filePaths": [
"short-var-declarations.go"
],
"patch": [
"diff --git a/short-var-declarations.go b/short-var-declarations.go",
"index 9209ec7..e69de29 100644",
"--- a/short-var-declarations.go",
"+++ b/short-var-declarations.go",
"@@ -1 +0,0 @@",
"-x, y := 3, 4"
],
"gitDir": "test/corpus/repos/go",
"shas": "6943eb4765b07143acf4bead143f4e9927d67e74..b47f159a4e69c481019748b1b4451ca5480b48ac"
}]

View File

@ -0,0 +1,742 @@
[{
"testCaseDescription": "go-single-import-declarations-insert-test",
"expectedResult": {
"changes": {
"single-import-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Added the \"net/http\" import statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
20
]
}
},
"summary": "Added the \"some/dsl\" import statement"
}
]
},
"errors": {
"single-import-declarations.go": [
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
28
]
}
},
"summary": "Added the 'import alias \"some/package\"' at line 3, column 1 - line 3, column 28"
}
]
}
},
"filePaths": [
"single-import-declarations.go"
],
"patch": [
"diff --git a/single-import-declarations.go b/single-import-declarations.go",
"index e69de29..e30eddb 100644",
"--- a/single-import-declarations.go",
"+++ b/single-import-declarations.go",
"@@ -0,0 +1,3 @@",
"+import \"net/http\"",
"+import . \"some/dsl\"",
"+import alias \"some/package\""
],
"gitDir": "test/corpus/repos/go",
"shas": "793a496d623444e8be55cfd3e3c1f3e7a1099406..8535b3bd21f463f65d277f11d98abfded0c74ec1"
}
,{
"testCaseDescription": "go-single-import-declarations-replacement-insert-test",
"expectedResult": {
"changes": {
"single-import-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
17
]
}
},
"summary": "Added the \"foo/bar\" import statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
21
]
}
},
"summary": "Added the \"types/dsl\" import statement"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
18
]
}
},
"summary": "Added the \"net/http\" import statement"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
20
]
}
},
"summary": "Added the \"some/dsl\" import statement"
}
]
},
"errors": {
"single-import-declarations.go": [
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
32
]
}
},
"summary": "Added the 'import alias \"awesome/packages\"' at line 3, column 1 - line 3, column 32"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
28
]
}
},
"summary": "Added the 'import alias \"some/package\"' at line 6, column 1 - line 6, column 28"
}
]
}
},
"filePaths": [
"single-import-declarations.go"
],
"patch": [
"diff --git a/single-import-declarations.go b/single-import-declarations.go",
"index e30eddb..a6141af 100644",
"--- a/single-import-declarations.go",
"+++ b/single-import-declarations.go",
"@@ -1,3 +1,9 @@",
"+import \"foo/bar\"",
"+import . \"types/dsl\"",
"+import alias \"awesome/packages\"",
"+import \"net/http\"",
"+import . \"some/dsl\"",
"+import alias \"some/package\"",
" import \"net/http\"",
" import . \"some/dsl\"",
" import alias \"some/package\""
],
"gitDir": "test/corpus/repos/go",
"shas": "8535b3bd21f463f65d277f11d98abfded0c74ec1..70e7e9c49e34fc8cd3b0b419c84cc73864f2c6e7"
}
,{
"testCaseDescription": "go-single-import-declarations-delete-insert-test",
"expectedResult": {
"changes": {
"single-import-declarations.go": [
{
"span": {
"replace": [
{
"start": [
1,
8
],
"end": [
1,
17
]
},
{
"start": [
1,
8
],
"end": [
1,
18
]
}
]
},
"summary": "Replaced the \"foo/bar\" string with the \"net/http\" string in the \"net/http\" import statement"
},
{
"span": {
"replace": [
{
"start": [
2,
10
],
"end": [
2,
21
]
},
{
"start": [
2,
10
],
"end": [
2,
20
]
}
]
},
"summary": "Replaced the \"types/dsl\" string with the \"some/dsl\" string in the \"some/dsl\" import statement"
},
{
"span": {
"replace": [
{
"start": [
3,
14
],
"end": [
3,
32
]
},
{
"start": [
3,
14
],
"end": [
3,
28
]
}
]
},
"summary": "Replaced the \"awesome/packages\" string with the \"some/package\" string"
}
]
},
"errors": {}
},
"filePaths": [
"single-import-declarations.go"
],
"patch": [
"diff --git a/single-import-declarations.go b/single-import-declarations.go",
"index a6141af..b54ad96 100644",
"--- a/single-import-declarations.go",
"+++ b/single-import-declarations.go",
"@@ -1,6 +1,6 @@",
"-import \"foo/bar\"",
"-import . \"types/dsl\"",
"-import alias \"awesome/packages\"",
"+import \"net/http\"",
"+import . \"some/dsl\"",
"+import alias \"some/package\"",
" import \"net/http\"",
" import . \"some/dsl\"",
" import alias \"some/package\""
],
"gitDir": "test/corpus/repos/go",
"shas": "70e7e9c49e34fc8cd3b0b419c84cc73864f2c6e7..a0af3129ebe2ee05ee2d8e68a0c095a8ea992b2f"
}
,{
"testCaseDescription": "go-single-import-declarations-replacement-test",
"expectedResult": {
"changes": {
"single-import-declarations.go": [
{
"span": {
"replace": [
{
"start": [
1,
8
],
"end": [
1,
18
]
},
{
"start": [
1,
8
],
"end": [
1,
17
]
}
]
},
"summary": "Replaced the \"net/http\" string with the \"foo/bar\" string in the \"foo/bar\" import statement"
},
{
"span": {
"replace": [
{
"start": [
2,
10
],
"end": [
2,
20
]
},
{
"start": [
2,
10
],
"end": [
2,
21
]
}
]
},
"summary": "Replaced the \"some/dsl\" string with the \"types/dsl\" string in the \"types/dsl\" import statement"
},
{
"span": {
"replace": [
{
"start": [
3,
14
],
"end": [
3,
28
]
},
{
"start": [
3,
14
],
"end": [
3,
32
]
}
]
},
"summary": "Replaced the \"some/package\" string with the \"awesome/packages\" string"
}
]
},
"errors": {}
},
"filePaths": [
"single-import-declarations.go"
],
"patch": [
"diff --git a/single-import-declarations.go b/single-import-declarations.go",
"index b54ad96..a6141af 100644",
"--- a/single-import-declarations.go",
"+++ b/single-import-declarations.go",
"@@ -1,6 +1,6 @@",
"-import \"net/http\"",
"-import . \"some/dsl\"",
"-import alias \"some/package\"",
"+import \"foo/bar\"",
"+import . \"types/dsl\"",
"+import alias \"awesome/packages\"",
" import \"net/http\"",
" import . \"some/dsl\"",
" import alias \"some/package\""
],
"gitDir": "test/corpus/repos/go",
"shas": "a0af3129ebe2ee05ee2d8e68a0c095a8ea992b2f..feb2a0ac79da8b6797559f7afad60f25c83c16eb"
}
,{
"testCaseDescription": "go-single-import-declarations-delete-replacement-test",
"expectedResult": {
"changes": {
"single-import-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
17
]
}
},
"summary": "Deleted the \"foo/bar\" import statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
21
]
}
},
"summary": "Deleted the \"types/dsl\" import statement"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
18
]
}
},
"summary": "Deleted the \"net/http\" import statement"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
5,
20
]
}
},
"summary": "Deleted the \"some/dsl\" import statement"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
17
]
}
},
"summary": "Added the \"foo/bar\" import statement"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
21
]
}
},
"summary": "Added the \"types/dsl\" import statement"
}
]
},
"errors": {
"single-import-declarations.go": [
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
32
]
}
},
"summary": "Deleted the 'import alias \"awesome/packages\"' at line 3, column 1 - line 3, column 32"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
6,
28
]
}
},
"summary": "Deleted the 'import alias \"some/package\"' at line 6, column 1 - line 6, column 28"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
32
]
}
},
"summary": "Added the 'import alias \"awesome/packages\"' at line 6, column 1 - line 6, column 32"
}
]
}
},
"filePaths": [
"single-import-declarations.go"
],
"patch": [
"diff --git a/single-import-declarations.go b/single-import-declarations.go",
"index a6141af..98c2392 100644",
"--- a/single-import-declarations.go",
"+++ b/single-import-declarations.go",
"@@ -1,9 +1,6 @@",
"-import \"foo/bar\"",
"-import . \"types/dsl\"",
"-import alias \"awesome/packages\"",
"-import \"net/http\"",
"-import . \"some/dsl\"",
"-import alias \"some/package\"",
" import \"net/http\"",
" import . \"some/dsl\"",
" import alias \"some/package\"",
"+import \"foo/bar\"",
"+import . \"types/dsl\"",
"+import alias \"awesome/packages\""
],
"gitDir": "test/corpus/repos/go",
"shas": "feb2a0ac79da8b6797559f7afad60f25c83c16eb..092a25430fea92313b4bf0929aa790de8dd9f972"
}
,{
"testCaseDescription": "go-single-import-declarations-delete-test",
"expectedResult": {
"changes": {
"single-import-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the \"net/http\" import statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
20
]
}
},
"summary": "Deleted the \"some/dsl\" import statement"
}
]
},
"errors": {
"single-import-declarations.go": [
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
28
]
}
},
"summary": "Deleted the 'import alias \"some/package\"' at line 3, column 1 - line 3, column 28"
}
]
}
},
"filePaths": [
"single-import-declarations.go"
],
"patch": [
"diff --git a/single-import-declarations.go b/single-import-declarations.go",
"index 98c2392..8af8c6d 100644",
"--- a/single-import-declarations.go",
"+++ b/single-import-declarations.go",
"@@ -1,6 +1,3 @@",
"-import \"net/http\"",
"-import . \"some/dsl\"",
"-import alias \"some/package\"",
" import \"foo/bar\"",
" import . \"types/dsl\"",
" import alias \"awesome/packages\""
],
"gitDir": "test/corpus/repos/go",
"shas": "092a25430fea92313b4bf0929aa790de8dd9f972..0d86b3da56f7c4362eab27035b89c90980c720f4"
}
,{
"testCaseDescription": "go-single-import-declarations-delete-rest-test",
"expectedResult": {
"changes": {
"single-import-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
17
]
}
},
"summary": "Deleted the \"foo/bar\" import statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
21
]
}
},
"summary": "Deleted the \"types/dsl\" import statement"
}
]
},
"errors": {
"single-import-declarations.go": [
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
32
]
}
},
"summary": "Deleted the 'import alias \"awesome/packages\"' at line 3, column 1 - line 3, column 32"
}
]
}
},
"filePaths": [
"single-import-declarations.go"
],
"patch": [
"diff --git a/single-import-declarations.go b/single-import-declarations.go",
"index 8af8c6d..e69de29 100644",
"--- a/single-import-declarations.go",
"+++ b/single-import-declarations.go",
"@@ -1,3 +0,0 @@",
"-import \"foo/bar\"",
"-import . \"types/dsl\"",
"-import alias \"awesome/packages\""
],
"gitDir": "test/corpus/repos/go",
"shas": "0d86b3da56f7c4362eab27035b89c90980c720f4..3a1a004fc80ca40433336cc35ed31bd631b4d589"
}]

View File

@ -0,0 +1,727 @@
[{
"testCaseDescription": "go-single-line-function-declarations-insert-test",
"expectedResult": {
"changes": {
"single-line-function-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Added the 'f1' function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
23
]
}
},
"summary": "Added the 'f2' function"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
24
]
}
},
"summary": "Added the 'f3' function"
}
]
},
"errors": {}
},
"filePaths": [
"single-line-function-declarations.go"
],
"patch": [
"diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
"index e69de29..3ac1720 100644",
"--- a/single-line-function-declarations.go",
"+++ b/single-line-function-declarations.go",
"@@ -0,0 +1,3 @@",
"+func f1() { a() }",
"+func f2() { a(); b() }",
"+func f3() { a(); b(); }"
],
"gitDir": "test/corpus/repos/go",
"shas": "03191e600093d2810fbd1457b8ce453f3a9696bf..b2cbca6a8f51baf420e79371f1f442411f276688"
}
,{
"testCaseDescription": "go-single-line-function-declarations-replacement-insert-test",
"expectedResult": {
"changes": {
"single-line-function-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Added the 'g1' function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
23
]
}
},
"summary": "Added the 'g2' function"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
24
]
}
},
"summary": "Added the 'g3' function"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
18
]
}
},
"summary": "Added the 'f1' function"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
23
]
}
},
"summary": "Added the 'f2' function"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
24
]
}
},
"summary": "Added the 'f3' function"
}
]
},
"errors": {}
},
"filePaths": [
"single-line-function-declarations.go"
],
"patch": [
"diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
"index 3ac1720..39e0696 100644",
"--- a/single-line-function-declarations.go",
"+++ b/single-line-function-declarations.go",
"@@ -1,3 +1,9 @@",
"+func g1() { a() }",
"+func g2() { a(); b() }",
"+func g3() { a(); b(); }",
"+func f1() { a() }",
"+func f2() { a(); b() }",
"+func f3() { a(); b(); }",
" func f1() { a() }",
" func f2() { a(); b() }",
" func f3() { a(); b(); }"
],
"gitDir": "test/corpus/repos/go",
"shas": "b2cbca6a8f51baf420e79371f1f442411f276688..ce98f2d5e6c31e6bcbb18a095df441522f26746b"
}
,{
"testCaseDescription": "go-single-line-function-declarations-delete-insert-test",
"expectedResult": {
"changes": {
"single-line-function-declarations.go": [
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
8
]
},
{
"start": [
1,
6
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced the 'g1' identifier with the 'f1' identifier in the f1 function"
},
{
"span": {
"replace": [
{
"start": [
2,
6
],
"end": [
2,
8
]
},
{
"start": [
2,
6
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the 'g2' identifier with the 'f2' identifier in the f2 function"
},
{
"span": {
"replace": [
{
"start": [
3,
6
],
"end": [
3,
8
]
},
{
"start": [
3,
6
],
"end": [
3,
8
]
}
]
},
"summary": "Replaced the 'g3' identifier with the 'f3' identifier in the f3 function"
}
]
},
"errors": {}
},
"filePaths": [
"single-line-function-declarations.go"
],
"patch": [
"diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
"index 39e0696..eec54a8 100644",
"--- a/single-line-function-declarations.go",
"+++ b/single-line-function-declarations.go",
"@@ -1,6 +1,6 @@",
"-func g1() { a() }",
"-func g2() { a(); b() }",
"-func g3() { a(); b(); }",
"+func f1() { a() }",
"+func f2() { a(); b() }",
"+func f3() { a(); b(); }",
" func f1() { a() }",
" func f2() { a(); b() }",
" func f3() { a(); b(); }"
],
"gitDir": "test/corpus/repos/go",
"shas": "ce98f2d5e6c31e6bcbb18a095df441522f26746b..fcf1179439dda87c096421c0c3b0c1761a30c5e4"
}
,{
"testCaseDescription": "go-single-line-function-declarations-replacement-test",
"expectedResult": {
"changes": {
"single-line-function-declarations.go": [
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
8
]
},
{
"start": [
1,
6
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced the 'f1' identifier with the 'g1' identifier in the g1 function"
},
{
"span": {
"replace": [
{
"start": [
2,
6
],
"end": [
2,
8
]
},
{
"start": [
2,
6
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the 'f2' identifier with the 'g2' identifier in the g2 function"
},
{
"span": {
"replace": [
{
"start": [
3,
6
],
"end": [
3,
8
]
},
{
"start": [
3,
6
],
"end": [
3,
8
]
}
]
},
"summary": "Replaced the 'f3' identifier with the 'g3' identifier in the g3 function"
}
]
},
"errors": {}
},
"filePaths": [
"single-line-function-declarations.go"
],
"patch": [
"diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
"index eec54a8..39e0696 100644",
"--- a/single-line-function-declarations.go",
"+++ b/single-line-function-declarations.go",
"@@ -1,6 +1,6 @@",
"-func f1() { a() }",
"-func f2() { a(); b() }",
"-func f3() { a(); b(); }",
"+func g1() { a() }",
"+func g2() { a(); b() }",
"+func g3() { a(); b(); }",
" func f1() { a() }",
" func f2() { a(); b() }",
" func f3() { a(); b(); }"
],
"gitDir": "test/corpus/repos/go",
"shas": "fcf1179439dda87c096421c0c3b0c1761a30c5e4..f5dd0898c6d86613943c800830a6abad17b8a690"
}
,{
"testCaseDescription": "go-single-line-function-declarations-delete-replacement-test",
"expectedResult": {
"changes": {
"single-line-function-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the 'g1' function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
23
]
}
},
"summary": "Deleted the 'g2' function"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
24
]
}
},
"summary": "Deleted the 'g3' function"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
18
]
}
},
"summary": "Deleted the 'f1' function"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
5,
23
]
}
},
"summary": "Deleted the 'f2' function"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
6,
24
]
}
},
"summary": "Deleted the 'f3' function"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
18
]
}
},
"summary": "Added the 'g1' function"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
23
]
}
},
"summary": "Added the 'g2' function"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
24
]
}
},
"summary": "Added the 'g3' function"
}
]
},
"errors": {}
},
"filePaths": [
"single-line-function-declarations.go"
],
"patch": [
"diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
"index 39e0696..7fcb3a1 100644",
"--- a/single-line-function-declarations.go",
"+++ b/single-line-function-declarations.go",
"@@ -1,9 +1,6 @@",
"-func g1() { a() }",
"-func g2() { a(); b() }",
"-func g3() { a(); b(); }",
"-func f1() { a() }",
"-func f2() { a(); b() }",
"-func f3() { a(); b(); }",
" func f1() { a() }",
" func f2() { a(); b() }",
" func f3() { a(); b(); }",
"+func g1() { a() }",
"+func g2() { a(); b() }",
"+func g3() { a(); b(); }"
],
"gitDir": "test/corpus/repos/go",
"shas": "f5dd0898c6d86613943c800830a6abad17b8a690..665255e90e5b3624568d36e439ae41c34978ad73"
}
,{
"testCaseDescription": "go-single-line-function-declarations-delete-test",
"expectedResult": {
"changes": {
"single-line-function-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the 'f1' function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
23
]
}
},
"summary": "Deleted the 'f2' function"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
24
]
}
},
"summary": "Deleted the 'f3' function"
}
]
},
"errors": {}
},
"filePaths": [
"single-line-function-declarations.go"
],
"patch": [
"diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
"index 7fcb3a1..ef4196f 100644",
"--- a/single-line-function-declarations.go",
"+++ b/single-line-function-declarations.go",
"@@ -1,6 +1,3 @@",
"-func f1() { a() }",
"-func f2() { a(); b() }",
"-func f3() { a(); b(); }",
" func g1() { a() }",
" func g2() { a(); b() }",
" func g3() { a(); b(); }"
],
"gitDir": "test/corpus/repos/go",
"shas": "665255e90e5b3624568d36e439ae41c34978ad73..d5e5fe07554182a4925eefe275b21350f71a414c"
}
,{
"testCaseDescription": "go-single-line-function-declarations-delete-rest-test",
"expectedResult": {
"changes": {
"single-line-function-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the 'g1' function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
23
]
}
},
"summary": "Deleted the 'g2' function"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
24
]
}
},
"summary": "Deleted the 'g3' function"
}
]
},
"errors": {}
},
"filePaths": [
"single-line-function-declarations.go"
],
"patch": [
"diff --git a/single-line-function-declarations.go b/single-line-function-declarations.go",
"index ef4196f..e69de29 100644",
"--- a/single-line-function-declarations.go",
"+++ b/single-line-function-declarations.go",
"@@ -1,3 +0,0 @@",
"-func g1() { a() }",
"-func g2() { a(); b() }",
"-func g3() { a(); b(); }"
],
"gitDir": "test/corpus/repos/go",
"shas": "d5e5fe07554182a4925eefe275b21350f71a414c..7e354b885fbffacfc60e09f0bd093cf0e6c38e3f"
}]

View File

@ -0,0 +1,812 @@
[{
"testCaseDescription": "go-slice-literals-insert-test",
"expectedResult": {
"changes": {
"slice-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Added the 's1' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
26
]
}
},
"summary": "Added the 's2' variable"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
6,
2
]
}
},
"summary": "Added the 's3' variable"
}
]
},
"errors": {}
},
"filePaths": [
"slice-literals.go"
],
"patch": [
"diff --git a/slice-literals.go b/slice-literals.go",
"index e69de29..9b1eb7a 100644",
"--- a/slice-literals.go",
"+++ b/slice-literals.go",
"@@ -0,0 +1,6 @@",
"+const s1 = []string{}",
"+const s2 = []string{\"hi\"}",
"+const s3 = []string{",
"+\"hi\",",
"+ \"hello\",",
"+}"
],
"gitDir": "test/corpus/repos/go",
"shas": "d7c85b9aedcbd3af69fdfe6a30e249364113d5e2..e5b39d883ee5c4845c6e84d7c6edec4ba14c5057"
}
,{
"testCaseDescription": "go-slice-literals-replacement-insert-test",
"expectedResult": {
"changes": {
"slice-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Added the 's1' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
29
]
}
},
"summary": "Added the 's2' variable"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
6,
2
]
}
},
"summary": "Added the 's3' variable"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
7,
22
]
}
},
"summary": "Added the 's1' variable"
},
{
"span": {
"insert": {
"start": [
8,
1
],
"end": [
8,
26
]
}
},
"summary": "Added the 's2' variable"
},
{
"span": {
"insert": {
"start": [
9,
1
],
"end": [
12,
2
]
}
},
"summary": "Added the 's3' variable"
}
]
},
"errors": {}
},
"filePaths": [
"slice-literals.go"
],
"patch": [
"diff --git a/slice-literals.go b/slice-literals.go",
"index 9b1eb7a..4555163 100644",
"--- a/slice-literals.go",
"+++ b/slice-literals.go",
"@@ -1,3 +1,15 @@",
"+const s1 = []string{\"sup\"}",
"+const s2 = []string{\"hello\"}",
"+const s3 = []string{",
"+\"bar\",",
"+ \"baz\",",
"+}",
"+const s1 = []string{}",
"+const s2 = []string{\"hi\"}",
"+const s3 = []string{",
"+\"hi\",",
"+ \"hello\",",
"+}",
" const s1 = []string{}",
" const s2 = []string{\"hi\"}",
" const s3 = []string{"
],
"gitDir": "test/corpus/repos/go",
"shas": "e5b39d883ee5c4845c6e84d7c6edec4ba14c5057..e92c35c4e9312dc3a6e804deda19c55347de6e06"
}
,{
"testCaseDescription": "go-slice-literals-delete-insert-test",
"expectedResult": {
"changes": {
"slice-literals.go": [
{
"span": {
"replace": [
{
"start": [
1,
21
],
"end": [
1,
26
]
},
{
"start": [
1,
20
],
"end": [
1,
22
]
}
]
},
"summary": "Replaced the \"sup\" string with the '{}' literal_value in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
2,
21
],
"end": [
2,
28
]
},
{
"start": [
2,
21
],
"end": [
2,
25
]
}
]
},
"summary": "Replaced the \"hello\" string with the \"hi\" string in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
4,
1
],
"end": [
4,
6
]
},
{
"start": [
4,
1
],
"end": [
4,
5
]
}
]
},
"summary": "Replaced the \"bar\" string with the \"hi\" string in the s3 variable"
},
{
"span": {
"replace": [
{
"start": [
5,
2
],
"end": [
5,
7
]
},
{
"start": [
5,
2
],
"end": [
5,
9
]
}
]
},
"summary": "Replaced the \"baz\" string with the \"hello\" string in the s3 variable"
}
]
},
"errors": {}
},
"filePaths": [
"slice-literals.go"
],
"patch": [
"diff --git a/slice-literals.go b/slice-literals.go",
"index 4555163..39a2067 100644",
"--- a/slice-literals.go",
"+++ b/slice-literals.go",
"@@ -1,8 +1,8 @@",
"-const s1 = []string{\"sup\"}",
"-const s2 = []string{\"hello\"}",
"+const s1 = []string{}",
"+const s2 = []string{\"hi\"}",
" const s3 = []string{",
"-\"bar\",",
"- \"baz\",",
"+\"hi\",",
"+ \"hello\",",
" }",
" const s1 = []string{}",
" const s2 = []string{\"hi\"}"
],
"gitDir": "test/corpus/repos/go",
"shas": "e92c35c4e9312dc3a6e804deda19c55347de6e06..4d6e51e7ba29099b0b91915fb889af994eec1795"
}
,{
"testCaseDescription": "go-slice-literals-replacement-test",
"expectedResult": {
"changes": {
"slice-literals.go": [
{
"span": {
"replace": [
{
"start": [
1,
20
],
"end": [
1,
22
]
},
{
"start": [
1,
21
],
"end": [
1,
26
]
}
]
},
"summary": "Replaced the '{}' literal_value with the \"sup\" string in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
2,
21
],
"end": [
2,
25
]
},
{
"start": [
2,
21
],
"end": [
2,
28
]
}
]
},
"summary": "Replaced the \"hi\" string with the \"hello\" string in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
4,
1
],
"end": [
4,
5
]
},
{
"start": [
4,
1
],
"end": [
4,
6
]
}
]
},
"summary": "Replaced the \"hi\" string with the \"bar\" string in the s3 variable"
},
{
"span": {
"replace": [
{
"start": [
5,
2
],
"end": [
5,
9
]
},
{
"start": [
5,
2
],
"end": [
5,
7
]
}
]
},
"summary": "Replaced the \"hello\" string with the \"baz\" string in the s3 variable"
}
]
},
"errors": {}
},
"filePaths": [
"slice-literals.go"
],
"patch": [
"diff --git a/slice-literals.go b/slice-literals.go",
"index 39a2067..4555163 100644",
"--- a/slice-literals.go",
"+++ b/slice-literals.go",
"@@ -1,8 +1,8 @@",
"-const s1 = []string{}",
"-const s2 = []string{\"hi\"}",
"+const s1 = []string{\"sup\"}",
"+const s2 = []string{\"hello\"}",
" const s3 = []string{",
"-\"hi\",",
"- \"hello\",",
"+\"bar\",",
"+ \"baz\",",
" }",
" const s1 = []string{}",
" const s2 = []string{\"hi\"}"
],
"gitDir": "test/corpus/repos/go",
"shas": "4d6e51e7ba29099b0b91915fb889af994eec1795..079faf0b3b47fde58866875a9a64813bc764950c"
}
,{
"testCaseDescription": "go-slice-literals-delete-replacement-test",
"expectedResult": {
"changes": {
"slice-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Deleted the 's1' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
29
]
}
},
"summary": "Deleted the 's2' variable"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
6,
2
]
}
},
"summary": "Deleted the 's3' variable"
},
{
"span": {
"delete": {
"start": [
7,
1
],
"end": [
7,
22
]
}
},
"summary": "Deleted the 's1' variable"
},
{
"span": {
"delete": {
"start": [
8,
1
],
"end": [
8,
26
]
}
},
"summary": "Deleted the 's2' variable"
},
{
"span": {
"delete": {
"start": [
9,
1
],
"end": [
12,
2
]
}
},
"summary": "Deleted the 's3' variable"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
7,
27
]
}
},
"summary": "Added the 's1' variable"
},
{
"span": {
"insert": {
"start": [
8,
1
],
"end": [
8,
29
]
}
},
"summary": "Added the 's2' variable"
},
{
"span": {
"insert": {
"start": [
9,
1
],
"end": [
12,
2
]
}
},
"summary": "Added the 's3' variable"
}
]
},
"errors": {}
},
"filePaths": [
"slice-literals.go"
],
"patch": [
"diff --git a/slice-literals.go b/slice-literals.go",
"index 4555163..d3fb29c 100644",
"--- a/slice-literals.go",
"+++ b/slice-literals.go",
"@@ -1,18 +1,12 @@",
"-const s1 = []string{\"sup\"}",
"-const s2 = []string{\"hello\"}",
"-const s3 = []string{",
"-\"bar\",",
"- \"baz\",",
"-}",
" const s1 = []string{}",
" const s2 = []string{\"hi\"}",
" const s3 = []string{",
" \"hi\",",
" \"hello\",",
" }",
"-const s1 = []string{}",
"-const s2 = []string{\"hi\"}",
"+const s1 = []string{\"sup\"}",
"+const s2 = []string{\"hello\"}",
" const s3 = []string{",
"-\"hi\",",
"- \"hello\",",
"+\"bar\",",
"+ \"baz\",",
" }"
],
"gitDir": "test/corpus/repos/go",
"shas": "079faf0b3b47fde58866875a9a64813bc764950c..705764c3224fe96e65bbb4e3ff1e8388e7219783"
}
,{
"testCaseDescription": "go-slice-literals-delete-test",
"expectedResult": {
"changes": {
"slice-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Deleted the 's1' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
26
]
}
},
"summary": "Deleted the 's2' variable"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
6,
2
]
}
},
"summary": "Deleted the 's3' variable"
}
]
},
"errors": {}
},
"filePaths": [
"slice-literals.go"
],
"patch": [
"diff --git a/slice-literals.go b/slice-literals.go",
"index d3fb29c..e3fd378 100644",
"--- a/slice-literals.go",
"+++ b/slice-literals.go",
"@@ -1,9 +1,3 @@",
"-const s1 = []string{}",
"-const s2 = []string{\"hi\"}",
"-const s3 = []string{",
"-\"hi\",",
"- \"hello\",",
"-}",
" const s1 = []string{\"sup\"}",
" const s2 = []string{\"hello\"}",
" const s3 = []string{"
],
"gitDir": "test/corpus/repos/go",
"shas": "705764c3224fe96e65bbb4e3ff1e8388e7219783..70be820be1a032a886aba1efaf386ea20e7e4636"
}
,{
"testCaseDescription": "go-slice-literals-delete-rest-test",
"expectedResult": {
"changes": {
"slice-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Deleted the 's1' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
29
]
}
},
"summary": "Deleted the 's2' variable"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
6,
2
]
}
},
"summary": "Deleted the 's3' variable"
}
]
},
"errors": {}
},
"filePaths": [
"slice-literals.go"
],
"patch": [
"diff --git a/slice-literals.go b/slice-literals.go",
"index e3fd378..e69de29 100644",
"--- a/slice-literals.go",
"+++ b/slice-literals.go",
"@@ -1,6 +0,0 @@",
"-const s1 = []string{\"sup\"}",
"-const s2 = []string{\"hello\"}",
"-const s3 = []string{",
"-\"bar\",",
"- \"baz\",",
"-}"
],
"gitDir": "test/corpus/repos/go",
"shas": "70be820be1a032a886aba1efaf386ea20e7e4636..0fff314fad0973ea89120a1ae3b7940e0f7866d2"
}]

View File

@ -0,0 +1,790 @@
[{
"testCaseDescription": "go-slice-types-insert-test",
"expectedResult": {
"changes": {
"slice-types.go": [
{
"span": {
"insert": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
1,
10
],
"end": [
1,
11
]
}
},
"summary": "Added the 'b' identifier"
},
{
"span": {
"insert": {
"start": [
2,
6
],
"end": [
2,
7
]
}
},
"summary": "Added the 'c' identifier"
},
{
"span": {
"insert": {
"start": [
2,
12
],
"end": [
2,
13
]
}
},
"summary": "Added the 'd' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"slice-types.go"
],
"patch": [
"diff --git a/slice-types.go b/slice-types.go",
"index e69de29..1b8dbe5 100644",
"--- a/slice-types.go",
"+++ b/slice-types.go",
"@@ -0,0 +1,2 @@",
"+type a []b",
"+type c [][]d"
],
"gitDir": "test/corpus/repos/go",
"shas": "ecbb5b13e89407c4e715ccf67e358e5fc18fbfe6..bb07f330c30f729c34488c5177bdbfa1adcda009"
}
,{
"testCaseDescription": "go-slice-types-replacement-insert-test",
"expectedResult": {
"changes": {
"slice-types.go": [
{
"span": {
"insert": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
1,
12
],
"end": [
1,
13
]
}
},
"summary": "Added the 'p' identifier"
},
{
"span": {
"insert": {
"start": [
2,
6
],
"end": [
2,
7
]
}
},
"summary": "Added the 'c' identifier"
},
{
"span": {
"insert": {
"start": [
2,
10
],
"end": [
2,
11
]
}
},
"summary": "Added the 'y' identifier"
},
{
"span": {
"insert": {
"start": [
3,
6
],
"end": [
3,
7
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
3,
10
],
"end": [
3,
11
]
}
},
"summary": "Added the 'b' identifier"
},
{
"span": {
"insert": {
"start": [
4,
6
],
"end": [
4,
7
]
}
},
"summary": "Added the 'c' identifier"
},
{
"span": {
"insert": {
"start": [
4,
12
],
"end": [
4,
13
]
}
},
"summary": "Added the 'd' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"slice-types.go"
],
"patch": [
"diff --git a/slice-types.go b/slice-types.go",
"index 1b8dbe5..d718ee8 100644",
"--- a/slice-types.go",
"+++ b/slice-types.go",
"@@ -1,2 +1,6 @@",
"+type a [][]p",
"+type c []y",
"+type a []b",
"+type c [][]d",
" type a []b",
" type c [][]d"
],
"gitDir": "test/corpus/repos/go",
"shas": "bb07f330c30f729c34488c5177bdbfa1adcda009..d8a446f73da85de672759677f695a3604809776c"
}
,{
"testCaseDescription": "go-slice-types-delete-insert-test",
"expectedResult": {
"changes": {
"slice-types.go": [
{
"span": {
"insert": {
"start": [
1,
10
],
"end": [
1,
11
]
}
},
"summary": "Added the 'b' identifier"
},
{
"span": {
"delete": {
"start": [
1,
12
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'p' identifier"
},
{
"span": {
"insert": {
"start": [
2,
12
],
"end": [
2,
13
]
}
},
"summary": "Added the 'd' identifier"
},
{
"span": {
"delete": {
"start": [
2,
10
],
"end": [
2,
11
]
}
},
"summary": "Deleted the 'y' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"slice-types.go"
],
"patch": [
"diff --git a/slice-types.go b/slice-types.go",
"index d718ee8..e6836eb 100644",
"--- a/slice-types.go",
"+++ b/slice-types.go",
"@@ -1,5 +1,5 @@",
"-type a [][]p",
"-type c []y",
"+type a []b",
"+type c [][]d",
" type a []b",
" type c [][]d",
" type a []b"
],
"gitDir": "test/corpus/repos/go",
"shas": "d8a446f73da85de672759677f695a3604809776c..10f227c053ced89f4057aa2b666319e8385c4ef1"
}
,{
"testCaseDescription": "go-slice-types-replacement-test",
"expectedResult": {
"changes": {
"slice-types.go": [
{
"span": {
"insert": {
"start": [
1,
12
],
"end": [
1,
13
]
}
},
"summary": "Added the 'p' identifier"
},
{
"span": {
"delete": {
"start": [
1,
10
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'b' identifier"
},
{
"span": {
"insert": {
"start": [
2,
10
],
"end": [
2,
11
]
}
},
"summary": "Added the 'y' identifier"
},
{
"span": {
"delete": {
"start": [
2,
12
],
"end": [
2,
13
]
}
},
"summary": "Deleted the 'd' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"slice-types.go"
],
"patch": [
"diff --git a/slice-types.go b/slice-types.go",
"index e6836eb..d718ee8 100644",
"--- a/slice-types.go",
"+++ b/slice-types.go",
"@@ -1,5 +1,5 @@",
"-type a []b",
"-type c [][]d",
"+type a [][]p",
"+type c []y",
" type a []b",
" type c [][]d",
" type a []b"
],
"gitDir": "test/corpus/repos/go",
"shas": "10f227c053ced89f4057aa2b666319e8385c4ef1..6a94a9051822b4344c1e02e1a4924d670f872acb"
}
,{
"testCaseDescription": "go-slice-types-delete-replacement-test",
"expectedResult": {
"changes": {
"slice-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
1,
12
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'p' identifier"
},
{
"span": {
"delete": {
"start": [
2,
6
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'c' identifier"
},
{
"span": {
"delete": {
"start": [
2,
10
],
"end": [
2,
11
]
}
},
"summary": "Deleted the 'y' identifier"
},
{
"span": {
"delete": {
"start": [
3,
6
],
"end": [
3,
7
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
3,
10
],
"end": [
3,
11
]
}
},
"summary": "Deleted the 'b' identifier"
},
{
"span": {
"delete": {
"start": [
4,
6
],
"end": [
4,
7
]
}
},
"summary": "Deleted the 'c' identifier"
},
{
"span": {
"delete": {
"start": [
4,
12
],
"end": [
4,
13
]
}
},
"summary": "Deleted the 'd' identifier"
},
{
"span": {
"insert": {
"start": [
3,
6
],
"end": [
3,
7
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
3,
12
],
"end": [
3,
13
]
}
},
"summary": "Added the 'p' identifier"
},
{
"span": {
"insert": {
"start": [
4,
6
],
"end": [
4,
7
]
}
},
"summary": "Added the 'c' identifier"
},
{
"span": {
"insert": {
"start": [
4,
10
],
"end": [
4,
11
]
}
},
"summary": "Added the 'y' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"slice-types.go"
],
"patch": [
"diff --git a/slice-types.go b/slice-types.go",
"index d718ee8..9f9c73f 100644",
"--- a/slice-types.go",
"+++ b/slice-types.go",
"@@ -1,6 +1,4 @@",
"-type a [][]p",
"-type c []y",
"-type a []b",
"-type c [][]d",
" type a []b",
" type c [][]d",
"+type a [][]p",
"+type c []y"
],
"gitDir": "test/corpus/repos/go",
"shas": "6a94a9051822b4344c1e02e1a4924d670f872acb..86ed7e6c1594c7c244da53bda19ab35fbe1a4431"
}
,{
"testCaseDescription": "go-slice-types-delete-test",
"expectedResult": {
"changes": {
"slice-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
1,
10
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'b' identifier"
},
{
"span": {
"delete": {
"start": [
2,
6
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'c' identifier"
},
{
"span": {
"delete": {
"start": [
2,
12
],
"end": [
2,
13
]
}
},
"summary": "Deleted the 'd' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"slice-types.go"
],
"patch": [
"diff --git a/slice-types.go b/slice-types.go",
"index 9f9c73f..964a319 100644",
"--- a/slice-types.go",
"+++ b/slice-types.go",
"@@ -1,4 +1,2 @@",
"-type a []b",
"-type c [][]d",
" type a [][]p",
" type c []y"
],
"gitDir": "test/corpus/repos/go",
"shas": "86ed7e6c1594c7c244da53bda19ab35fbe1a4431..86be4da43ace61e52cc61914cc60bed850f3c0cc"
}
,{
"testCaseDescription": "go-slice-types-delete-rest-test",
"expectedResult": {
"changes": {
"slice-types.go": [
{
"span": {
"delete": {
"start": [
1,
6
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
1,
12
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'p' identifier"
},
{
"span": {
"delete": {
"start": [
2,
6
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'c' identifier"
},
{
"span": {
"delete": {
"start": [
2,
10
],
"end": [
2,
11
]
}
},
"summary": "Deleted the 'y' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"slice-types.go"
],
"patch": [
"diff --git a/slice-types.go b/slice-types.go",
"index 964a319..e69de29 100644",
"--- a/slice-types.go",
"+++ b/slice-types.go",
"@@ -1,2 +0,0 @@",
"-type a [][]p",
"-type c []y"
],
"gitDir": "test/corpus/repos/go",
"shas": "86be4da43ace61e52cc61914cc60bed850f3c0cc..1e96ae060f06444539a3cfa853d7de2f58dd8eac"
}]

View File

@ -0,0 +1,560 @@
[{
"testCaseDescription": "go-string-literals-insert-test",
"expectedResult": {
"changes": {
"string-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"string-literals.go"
],
"patch": [
"diff --git a/string-literals.go b/string-literals.go",
"index e69de29..90ac543 100644",
"--- a/string-literals.go",
"+++ b/string-literals.go",
"@@ -0,0 +1,4 @@",
"+const (",
"+a = \"0\"",
"+b = \"hello world\"",
"+)"
],
"gitDir": "test/corpus/repos/go",
"shas": "740c6c6b1390c86d2f179d9d31f010916292861a..9698847d1ada590968dad5fc427c1758590173f2"
}
,{
"testCaseDescription": "go-string-literals-replacement-insert-test",
"expectedResult": {
"changes": {
"string-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'b' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"string-literals.go"
],
"patch": [
"diff --git a/string-literals.go b/string-literals.go",
"index 90ac543..a781ce7 100644",
"--- a/string-literals.go",
"+++ b/string-literals.go",
"@@ -1,4 +1,12 @@",
" const (",
"+a = \"2\"",
"+b = \"hi\"",
"+)",
"+const (",
"+a = \"0\"",
"+b = \"hello world\"",
"+)",
"+const (",
" a = \"0\"",
" b = \"hello world\"",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "9698847d1ada590968dad5fc427c1758590173f2..e8867a66d6757f4af01fd07689f3c8a879acdc80"
}
,{
"testCaseDescription": "go-string-literals-delete-insert-test",
"expectedResult": {
"changes": {
"string-literals.go": [
{
"span": {
"replace": [
{
"start": [
2,
5
],
"end": [
2,
8
]
},
{
"start": [
2,
5
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the \"2\" string with the \"0\" string in the a variable"
},
{
"span": {
"replace": [
{
"start": [
3,
5
],
"end": [
3,
9
]
},
{
"start": [
3,
5
],
"end": [
3,
18
]
}
]
},
"summary": "Replaced the \"hi\" string with the \"hello world\" string in the b variable"
}
]
},
"errors": {}
},
"filePaths": [
"string-literals.go"
],
"patch": [
"diff --git a/string-literals.go b/string-literals.go",
"index a781ce7..e7b83ba 100644",
"--- a/string-literals.go",
"+++ b/string-literals.go",
"@@ -1,6 +1,6 @@",
" const (",
"-a = \"2\"",
"-b = \"hi\"",
"+a = \"0\"",
"+b = \"hello world\"",
" )",
" const (",
" a = \"0\""
],
"gitDir": "test/corpus/repos/go",
"shas": "e8867a66d6757f4af01fd07689f3c8a879acdc80..afb562067673bb91dc8df3e801ccb22827b8061e"
}
,{
"testCaseDescription": "go-string-literals-replacement-test",
"expectedResult": {
"changes": {
"string-literals.go": [
{
"span": {
"replace": [
{
"start": [
2,
5
],
"end": [
2,
8
]
},
{
"start": [
2,
5
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the \"0\" string with the \"2\" string in the a variable"
},
{
"span": {
"replace": [
{
"start": [
3,
5
],
"end": [
3,
18
]
},
{
"start": [
3,
5
],
"end": [
3,
9
]
}
]
},
"summary": "Replaced the \"hello world\" string with the \"hi\" string in the b variable"
}
]
},
"errors": {}
},
"filePaths": [
"string-literals.go"
],
"patch": [
"diff --git a/string-literals.go b/string-literals.go",
"index e7b83ba..a781ce7 100644",
"--- a/string-literals.go",
"+++ b/string-literals.go",
"@@ -1,6 +1,6 @@",
" const (",
"-a = \"0\"",
"-b = \"hello world\"",
"+a = \"2\"",
"+b = \"hi\"",
" )",
" const (",
" a = \"0\""
],
"gitDir": "test/corpus/repos/go",
"shas": "afb562067673bb91dc8df3e801ccb22827b8061e..5345aa6a6eba226eb0cc8bce11c1073b3afea305"
}
,{
"testCaseDescription": "go-string-literals-delete-replacement-test",
"expectedResult": {
"changes": {
"string-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"string-literals.go"
],
"patch": [
"diff --git a/string-literals.go b/string-literals.go",
"index a781ce7..38c651f 100644",
"--- a/string-literals.go",
"+++ b/string-literals.go",
"@@ -1,12 +1,8 @@",
" const (",
"-a = \"2\"",
"-b = \"hi\"",
"-)",
"-const (",
" a = \"0\"",
" b = \"hello world\"",
" )",
" const (",
"-a = \"0\"",
"-b = \"hello world\"",
"+a = \"2\"",
"+b = \"hi\"",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "5345aa6a6eba226eb0cc8bce11c1073b3afea305..38c2ea7acc57af4f85190210c284999e77853ab5"
}
,{
"testCaseDescription": "go-string-literals-delete-test",
"expectedResult": {
"changes": {
"string-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"string-literals.go"
],
"patch": [
"diff --git a/string-literals.go b/string-literals.go",
"index 38c651f..f70bc80 100644",
"--- a/string-literals.go",
"+++ b/string-literals.go",
"@@ -1,8 +1,4 @@",
" const (",
"-a = \"0\"",
"-b = \"hello world\"",
"-)",
"-const (",
" a = \"2\"",
" b = \"hi\"",
" )"
],
"gitDir": "test/corpus/repos/go",
"shas": "38c2ea7acc57af4f85190210c284999e77853ab5..4fb5f349e5afea8321390fc01cd64c5e894a987c"
}
,{
"testCaseDescription": "go-string-literals-delete-rest-test",
"expectedResult": {
"changes": {
"string-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'b' variable"
}
]
},
"errors": {}
},
"filePaths": [
"string-literals.go"
],
"patch": [
"diff --git a/string-literals.go b/string-literals.go",
"index f70bc80..e69de29 100644",
"--- a/string-literals.go",
"+++ b/string-literals.go",
"@@ -1,4 +0,0 @@",
"-const (",
"-a = \"2\"",
"-b = \"hi\"",
"-)"
],
"gitDir": "test/corpus/repos/go",
"shas": "4fb5f349e5afea8321390fc01cd64c5e894a987c..d7c85b9aedcbd3af69fdfe6a30e249364113d5e2"
}]

View File

@ -0,0 +1,865 @@
[{
"testCaseDescription": "go-struct-literals-insert-test",
"expectedResult": {
"changes": {
"struct-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 's1' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
32
]
}
},
"summary": "Added the 's2' variable"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
23
]
}
},
"summary": "Added the 's3' variable"
}
]
},
"errors": {}
},
"filePaths": [
"struct-literals.go"
],
"patch": [
"diff --git a/struct-literals.go b/struct-literals.go",
"index e69de29..f949dbb 100644",
"--- a/struct-literals.go",
"+++ b/struct-literals.go",
"@@ -0,0 +1,6 @@",
"+const s1 = Person{",
"+name: \"Frank\",",
"+Age: \"5 months\",",
"+}",
"+const s2 = struct{i int;}{i: 5}",
"+const s3 = time.Time{}"
],
"gitDir": "test/corpus/repos/go",
"shas": "821d52811675ea17dd00d79b0f4e082376b97afc..f95070fc9ad568a31f1f26f714fca1b38e518d0f"
}
,{
"testCaseDescription": "go-struct-literals-replacement-insert-test",
"expectedResult": {
"changes": {
"struct-literals.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 's1' variable"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
34
]
}
},
"summary": "Added the 's2' variable"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
24
]
}
},
"summary": "Added the 's3' variable"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
10,
2
]
}
},
"summary": "Added the 's1' variable"
},
{
"span": {
"insert": {
"start": [
11,
1
],
"end": [
11,
32
]
}
},
"summary": "Added the 's2' variable"
},
{
"span": {
"insert": {
"start": [
12,
1
],
"end": [
12,
23
]
}
},
"summary": "Added the 's3' variable"
}
]
},
"errors": {}
},
"filePaths": [
"struct-literals.go"
],
"patch": [
"diff --git a/struct-literals.go b/struct-literals.go",
"index f949dbb..c6a242e 100644",
"--- a/struct-literals.go",
"+++ b/struct-literals.go",
"@@ -1,3 +1,15 @@",
"+const s1 = Dog{",
"+name: \"Frank\",",
"+Age: \"5 months\",",
"+}",
"+const s2 = struct{i float;}{j: 6}",
"+const s3 = time.Month{}",
"+const s1 = Person{",
"+name: \"Frank\",",
"+Age: \"5 months\",",
"+}",
"+const s2 = struct{i int;}{i: 5}",
"+const s3 = time.Time{}",
" const s1 = Person{",
" name: \"Frank\",",
" Age: \"5 months\","
],
"gitDir": "test/corpus/repos/go",
"shas": "f95070fc9ad568a31f1f26f714fca1b38e518d0f..69ccd2c4c78c59c85cec84a8f602af771f81b441"
}
,{
"testCaseDescription": "go-struct-literals-delete-insert-test",
"expectedResult": {
"changes": {
"struct-literals.go": [
{
"span": {
"replace": [
{
"start": [
1,
12
],
"end": [
1,
15
]
},
{
"start": [
1,
12
],
"end": [
1,
18
]
}
]
},
"summary": "Replaced the 'Dog' identifier with the 'Person' identifier in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
5,
21
],
"end": [
5,
26
]
},
{
"start": [
5,
21
],
"end": [
5,
24
]
}
]
},
"summary": "Replaced the 'float' identifier with the 'int' identifier in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
5,
29
],
"end": [
5,
30
]
},
{
"start": [
5,
27
],
"end": [
5,
28
]
}
]
},
"summary": "Replaced the 'j' identifier with the 'i' identifier in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
5,
32
],
"end": [
5,
33
]
},
{
"start": [
5,
30
],
"end": [
5,
31
]
}
]
},
"summary": "Replaced '6' with '5' in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
6,
17
],
"end": [
6,
22
]
},
{
"start": [
6,
17
],
"end": [
6,
21
]
}
]
},
"summary": "Replaced the 'Month' identifier with the 'Time' identifier in the s3 variable"
}
]
},
"errors": {}
},
"filePaths": [
"struct-literals.go"
],
"patch": [
"diff --git a/struct-literals.go b/struct-literals.go",
"index c6a242e..680652e 100644",
"--- a/struct-literals.go",
"+++ b/struct-literals.go",
"@@ -1,9 +1,9 @@",
"-const s1 = Dog{",
"+const s1 = Person{",
" name: \"Frank\",",
" Age: \"5 months\",",
" }",
"-const s2 = struct{i float;}{j: 6}",
"-const s3 = time.Month{}",
"+const s2 = struct{i int;}{i: 5}",
"+const s3 = time.Time{}",
" const s1 = Person{",
" name: \"Frank\",",
" Age: \"5 months\","
],
"gitDir": "test/corpus/repos/go",
"shas": "69ccd2c4c78c59c85cec84a8f602af771f81b441..18672cd492f61710467d45f0a0404eda67ef786f"
}
,{
"testCaseDescription": "go-struct-literals-replacement-test",
"expectedResult": {
"changes": {
"struct-literals.go": [
{
"span": {
"replace": [
{
"start": [
1,
12
],
"end": [
1,
18
]
},
{
"start": [
1,
12
],
"end": [
1,
15
]
}
]
},
"summary": "Replaced the 'Person' identifier with the 'Dog' identifier in the s1 variable"
},
{
"span": {
"replace": [
{
"start": [
5,
21
],
"end": [
5,
24
]
},
{
"start": [
5,
21
],
"end": [
5,
26
]
}
]
},
"summary": "Replaced the 'int' identifier with the 'float' identifier in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
5,
27
],
"end": [
5,
28
]
},
{
"start": [
5,
29
],
"end": [
5,
30
]
}
]
},
"summary": "Replaced the 'i' identifier with the 'j' identifier in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
5,
30
],
"end": [
5,
31
]
},
{
"start": [
5,
32
],
"end": [
5,
33
]
}
]
},
"summary": "Replaced '5' with '6' in the s2 variable"
},
{
"span": {
"replace": [
{
"start": [
6,
17
],
"end": [
6,
21
]
},
{
"start": [
6,
17
],
"end": [
6,
22
]
}
]
},
"summary": "Replaced the 'Time' identifier with the 'Month' identifier in the s3 variable"
}
]
},
"errors": {}
},
"filePaths": [
"struct-literals.go"
],
"patch": [
"diff --git a/struct-literals.go b/struct-literals.go",
"index 680652e..c6a242e 100644",
"--- a/struct-literals.go",
"+++ b/struct-literals.go",
"@@ -1,9 +1,9 @@",
"-const s1 = Person{",
"+const s1 = Dog{",
" name: \"Frank\",",
" Age: \"5 months\",",
" }",
"-const s2 = struct{i int;}{i: 5}",
"-const s3 = time.Time{}",
"+const s2 = struct{i float;}{j: 6}",
"+const s3 = time.Month{}",
" const s1 = Person{",
" name: \"Frank\",",
" Age: \"5 months\","
],
"gitDir": "test/corpus/repos/go",
"shas": "18672cd492f61710467d45f0a0404eda67ef786f..3a6f5dd454cb71872be3981556590819ca08e4cd"
}
,{
"testCaseDescription": "go-struct-literals-delete-replacement-test",
"expectedResult": {
"changes": {
"struct-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 's1' variable"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
5,
34
]
}
},
"summary": "Deleted the 's2' variable"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
6,
24
]
}
},
"summary": "Deleted the 's3' variable"
},
{
"span": {
"delete": {
"start": [
7,
1
],
"end": [
10,
2
]
}
},
"summary": "Deleted the 's1' variable"
},
{
"span": {
"delete": {
"start": [
11,
1
],
"end": [
11,
32
]
}
},
"summary": "Deleted the 's2' variable"
},
{
"span": {
"delete": {
"start": [
12,
1
],
"end": [
12,
23
]
}
},
"summary": "Deleted the 's3' variable"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
10,
2
]
}
},
"summary": "Added the 's1' variable"
},
{
"span": {
"insert": {
"start": [
11,
1
],
"end": [
11,
34
]
}
},
"summary": "Added the 's2' variable"
},
{
"span": {
"insert": {
"start": [
12,
1
],
"end": [
12,
24
]
}
},
"summary": "Added the 's3' variable"
}
]
},
"errors": {}
},
"filePaths": [
"struct-literals.go"
],
"patch": [
"diff --git a/struct-literals.go b/struct-literals.go",
"index c6a242e..5aaf236 100644",
"--- a/struct-literals.go",
"+++ b/struct-literals.go",
"@@ -1,18 +1,12 @@",
"-const s1 = Dog{",
"-name: \"Frank\",",
"-Age: \"5 months\",",
"-}",
"-const s2 = struct{i float;}{j: 6}",
"-const s3 = time.Month{}",
" const s1 = Person{",
" name: \"Frank\",",
" Age: \"5 months\",",
" }",
" const s2 = struct{i int;}{i: 5}",
" const s3 = time.Time{}",
"-const s1 = Person{",
"+const s1 = Dog{",
" name: \"Frank\",",
" Age: \"5 months\",",
" }",
"-const s2 = struct{i int;}{i: 5}",
"-const s3 = time.Time{}",
"+const s2 = struct{i float;}{j: 6}",
"+const s3 = time.Month{}"
],
"gitDir": "test/corpus/repos/go",
"shas": "3a6f5dd454cb71872be3981556590819ca08e4cd..3b3bf2627d244b37a62ebdc901f39bccb4fa1a8d"
}
,{
"testCaseDescription": "go-struct-literals-delete-test",
"expectedResult": {
"changes": {
"struct-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 's1' variable"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
5,
32
]
}
},
"summary": "Deleted the 's2' variable"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
6,
23
]
}
},
"summary": "Deleted the 's3' variable"
}
]
},
"errors": {}
},
"filePaths": [
"struct-literals.go"
],
"patch": [
"diff --git a/struct-literals.go b/struct-literals.go",
"index 5aaf236..9f5ac64 100644",
"--- a/struct-literals.go",
"+++ b/struct-literals.go",
"@@ -1,9 +1,3 @@",
"-const s1 = Person{",
"-name: \"Frank\",",
"-Age: \"5 months\",",
"-}",
"-const s2 = struct{i int;}{i: 5}",
"-const s3 = time.Time{}",
" const s1 = Dog{",
" name: \"Frank\",",
" Age: \"5 months\","
],
"gitDir": "test/corpus/repos/go",
"shas": "3b3bf2627d244b37a62ebdc901f39bccb4fa1a8d..444283cd200e082d9380eae6c996da8d96be594d"
}
,{
"testCaseDescription": "go-struct-literals-delete-rest-test",
"expectedResult": {
"changes": {
"struct-literals.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 's1' variable"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
5,
34
]
}
},
"summary": "Deleted the 's2' variable"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
6,
24
]
}
},
"summary": "Deleted the 's3' variable"
}
]
},
"errors": {}
},
"filePaths": [
"struct-literals.go"
],
"patch": [
"diff --git a/struct-literals.go b/struct-literals.go",
"index 9f5ac64..e69de29 100644",
"--- a/struct-literals.go",
"+++ b/struct-literals.go",
"@@ -1,6 +0,0 @@",
"-const s1 = Dog{",
"-name: \"Frank\",",
"-Age: \"5 months\",",
"-}",
"-const s2 = struct{i float;}{j: 6}",
"-const s3 = time.Month{}"
],
"gitDir": "test/corpus/repos/go",
"shas": "444283cd200e082d9380eae6c996da8d96be594d..7fd6dea031e26a02c1743a205dc1489a7e050468"
}]

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,657 @@
[{
"testCaseDescription": "go-switch-statements-insert-test",
"expectedResult": {
"changes": {
"switch-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'branch' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"switch-statements.go"
],
"patch": [
"diff --git a/switch-statements.go b/switch-statements.go",
"index e69de29..e444d1e 100644",
"--- a/switch-statements.go",
"+++ b/switch-statements.go",
"@@ -0,0 +1,4 @@",
"+switch { case x < y: f1()",
"+case x < z: g()",
"+case x == 4: h()",
"+}"
],
"gitDir": "test/corpus/repos/go",
"shas": "25238a93bb3b92d4e2609c44f320e44fd9f4b537..fa7dbbfc36d0753d67461de33813be5492beefc2"
}
,{
"testCaseDescription": "go-switch-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"switch-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Added the 'branch' switch statement"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'branch' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"switch-statements.go"
],
"patch": [
"diff --git a/switch-statements.go b/switch-statements.go",
"index e444d1e..e2e5cf3 100644",
"--- a/switch-statements.go",
"+++ b/switch-statements.go",
"@@ -1,3 +1,11 @@",
"+switch { case a < b: f1()",
"+case c < d: g()",
"+case e == 4: f()",
"+}",
"+switch { case x < y: f1()",
"+case x < z: g()",
"+case x == 4: h()",
"+}",
" switch { case x < y: f1()",
" case x < z: g()",
" case x == 4: h()"
],
"gitDir": "test/corpus/repos/go",
"shas": "fa7dbbfc36d0753d67461de33813be5492beefc2..f989edd6b885f1d71d4c0caa94c2f66647dd74d2"
}
,{
"testCaseDescription": "go-switch-statements-delete-insert-test",
"expectedResult": {
"changes": {
"switch-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
15
],
"end": [
1,
16
]
},
{
"start": [
1,
15
],
"end": [
1,
16
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'x' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
1,
19
],
"end": [
1,
20
]
},
{
"start": [
1,
19
],
"end": [
1,
20
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'y' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
2,
6
],
"end": [
2,
7
]
},
{
"start": [
2,
6
],
"end": [
2,
7
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'x' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
2,
10
],
"end": [
2,
11
]
},
{
"start": [
2,
10
],
"end": [
2,
11
]
}
]
},
"summary": "Replaced the 'd' identifier with the 'z' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
3,
6
],
"end": [
3,
7
]
},
{
"start": [
3,
6
],
"end": [
3,
7
]
}
]
},
"summary": "Replaced the 'e' identifier with the 'x' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
3,
14
],
"end": [
3,
15
]
},
{
"start": [
3,
14
],
"end": [
3,
15
]
}
]
},
"summary": "Replaced the 'f' identifier with the 'h' identifier in the h() function call"
}
]
},
"errors": {}
},
"filePaths": [
"switch-statements.go"
],
"patch": [
"diff --git a/switch-statements.go b/switch-statements.go",
"index e2e5cf3..143707d 100644",
"--- a/switch-statements.go",
"+++ b/switch-statements.go",
"@@ -1,6 +1,6 @@",
"-switch { case a < b: f1()",
"-case c < d: g()",
"-case e == 4: f()",
"+switch { case x < y: f1()",
"+case x < z: g()",
"+case x == 4: h()",
" }",
" switch { case x < y: f1()",
" case x < z: g()"
],
"gitDir": "test/corpus/repos/go",
"shas": "f989edd6b885f1d71d4c0caa94c2f66647dd74d2..573eec4554298c107f0fec98c9a0a9447e01419b"
}
,{
"testCaseDescription": "go-switch-statements-replacement-test",
"expectedResult": {
"changes": {
"switch-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
15
],
"end": [
1,
16
]
},
{
"start": [
1,
15
],
"end": [
1,
16
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'a' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
1,
19
],
"end": [
1,
20
]
},
{
"start": [
1,
19
],
"end": [
1,
20
]
}
]
},
"summary": "Replaced the 'y' identifier with the 'b' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
2,
6
],
"end": [
2,
7
]
},
{
"start": [
2,
6
],
"end": [
2,
7
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'c' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
2,
10
],
"end": [
2,
11
]
},
{
"start": [
2,
10
],
"end": [
2,
11
]
}
]
},
"summary": "Replaced the 'z' identifier with the 'd' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
3,
6
],
"end": [
3,
7
]
},
{
"start": [
3,
6
],
"end": [
3,
7
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'e' identifier in the 'branch' switch statement"
},
{
"span": {
"replace": [
{
"start": [
3,
14
],
"end": [
3,
15
]
},
{
"start": [
3,
14
],
"end": [
3,
15
]
}
]
},
"summary": "Replaced the 'h' identifier with the 'f' identifier in the f() function call"
}
]
},
"errors": {}
},
"filePaths": [
"switch-statements.go"
],
"patch": [
"diff --git a/switch-statements.go b/switch-statements.go",
"index 143707d..e2e5cf3 100644",
"--- a/switch-statements.go",
"+++ b/switch-statements.go",
"@@ -1,6 +1,6 @@",
"-switch { case x < y: f1()",
"-case x < z: g()",
"-case x == 4: h()",
"+switch { case a < b: f1()",
"+case c < d: g()",
"+case e == 4: f()",
" }",
" switch { case x < y: f1()",
" case x < z: g()"
],
"gitDir": "test/corpus/repos/go",
"shas": "573eec4554298c107f0fec98c9a0a9447e01419b..a5db4da268b58006496efe5e952f07dc3d2320db"
}
,{
"testCaseDescription": "go-switch-statements-delete-replacement-test",
"expectedResult": {
"changes": {
"switch-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'branch' switch statement"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Deleted the 'branch' switch statement"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
8,
2
]
}
},
"summary": "Added the 'branch' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"switch-statements.go"
],
"patch": [
"diff --git a/switch-statements.go b/switch-statements.go",
"index e2e5cf3..6989d28 100644",
"--- a/switch-statements.go",
"+++ b/switch-statements.go",
"@@ -1,12 +1,8 @@",
"-switch { case a < b: f1()",
"-case c < d: g()",
"-case e == 4: f()",
"-}",
" switch { case x < y: f1()",
" case x < z: g()",
" case x == 4: h()",
" }",
"-switch { case x < y: f1()",
"-case x < z: g()",
"-case x == 4: h()",
"+switch { case a < b: f1()",
"+case c < d: g()",
"+case e == 4: f()",
" }"
],
"gitDir": "test/corpus/repos/go",
"shas": "a5db4da268b58006496efe5e952f07dc3d2320db..fd7487d4446fc6042d809a0cdb59deee1ff4ae04"
}
,{
"testCaseDescription": "go-switch-statements-delete-test",
"expectedResult": {
"changes": {
"switch-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'branch' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"switch-statements.go"
],
"patch": [
"diff --git a/switch-statements.go b/switch-statements.go",
"index 6989d28..eff174f 100644",
"--- a/switch-statements.go",
"+++ b/switch-statements.go",
"@@ -1,7 +1,3 @@",
"-switch { case x < y: f1()",
"-case x < z: g()",
"-case x == 4: h()",
"-}",
" switch { case a < b: f1()",
" case c < d: g()",
" case e == 4: f()"
],
"gitDir": "test/corpus/repos/go",
"shas": "fd7487d4446fc6042d809a0cdb59deee1ff4ae04..e98129fc667415197589dc420de58f3b3d2886fc"
}
,{
"testCaseDescription": "go-switch-statements-delete-rest-test",
"expectedResult": {
"changes": {
"switch-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
4,
2
]
}
},
"summary": "Deleted the 'branch' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"switch-statements.go"
],
"patch": [
"diff --git a/switch-statements.go b/switch-statements.go",
"index eff174f..e69de29 100644",
"--- a/switch-statements.go",
"+++ b/switch-statements.go",
"@@ -1,4 +0,0 @@",
"-switch { case a < b: f1()",
"-case c < d: g()",
"-case e == 4: f()",
"-}"
],
"gitDir": "test/corpus/repos/go",
"shas": "e98129fc667415197589dc420de58f3b3d2886fc..d0a9400c6fb3a520721068d06591be6dba11ccee"
}]

View File

@ -0,0 +1,455 @@
[{
"testCaseDescription": "go-type-assertion-expressions-insert-test",
"expectedResult": {
"changes": {
"type-assertion-expressions.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'x.(z.Person)' type assertion statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-assertion-expressions.go"
],
"patch": [
"diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
"index e69de29..0765038 100644",
"--- a/type-assertion-expressions.go",
"+++ b/type-assertion-expressions.go",
"@@ -0,0 +1 @@",
"+x.(z.Person)"
],
"gitDir": "test/corpus/repos/go",
"shas": "fff4b5e3aa207b2f8d5dc8ddb03b550f79baec95..7cdaee711fdf7f7a97fc3269e28626252a4dc3dc"
}
,{
"testCaseDescription": "go-type-assertion-expressions-replacement-insert-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": {
"insert": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Added the 'x.(z.Person)' type assertion statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-assertion-expressions.go"
],
"patch": [
"diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
"index 0765038..56239fb 100644",
"--- a/type-assertion-expressions.go",
"+++ b/type-assertion-expressions.go",
"@@ -1 +1,3 @@",
"+b.(c.Dog)",
"+x.(z.Person)",
" x.(z.Person)"
],
"gitDir": "test/corpus/repos/go",
"shas": "7cdaee711fdf7f7a97fc3269e28626252a4dc3dc..2bccd29b12d301d0fa0744e890ae3afdba1f43bc"
}
,{
"testCaseDescription": "go-type-assertion-expressions-delete-insert-test",
"expectedResult": {
"changes": {
"type-assertion-expressions.go": [
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
2
]
},
{
"start": [
1,
1
],
"end": [
1,
2
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'x' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
4
],
"end": [
1,
5
]
},
{
"start": [
1,
4
],
"end": [
1,
5
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'z' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
9
]
},
{
"start": [
1,
6
],
"end": [
1,
12
]
}
]
},
"summary": "Replaced the 'Dog' identifier with the 'Person' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"type-assertion-expressions.go"
],
"patch": [
"diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
"index 56239fb..de94018 100644",
"--- a/type-assertion-expressions.go",
"+++ b/type-assertion-expressions.go",
"@@ -1,3 +1,3 @@",
"-b.(c.Dog)",
"+x.(z.Person)",
" x.(z.Person)",
" x.(z.Person)"
],
"gitDir": "test/corpus/repos/go",
"shas": "2bccd29b12d301d0fa0744e890ae3afdba1f43bc..b774e03f1513e1139f22bbc3e116e2ff17168247"
}
,{
"testCaseDescription": "go-type-assertion-expressions-replacement-test",
"expectedResult": {
"changes": {
"type-assertion-expressions.go": [
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
2
]
},
{
"start": [
1,
1
],
"end": [
1,
2
]
}
]
},
"summary": "Replaced the 'x' identifier with the 'b' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
4
],
"end": [
1,
5
]
},
{
"start": [
1,
4
],
"end": [
1,
5
]
}
]
},
"summary": "Replaced the 'z' identifier with the 'c' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
12
]
},
{
"start": [
1,
6
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'Person' identifier with the 'Dog' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"type-assertion-expressions.go"
],
"patch": [
"diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
"index de94018..56239fb 100644",
"--- a/type-assertion-expressions.go",
"+++ b/type-assertion-expressions.go",
"@@ -1,3 +1,3 @@",
"-x.(z.Person)",
"+b.(c.Dog)",
" x.(z.Person)",
" x.(z.Person)"
],
"gitDir": "test/corpus/repos/go",
"shas": "b774e03f1513e1139f22bbc3e116e2ff17168247..596b57a4b9a75038c3f5594caa3561a52de5dc16"
}
,{
"testCaseDescription": "go-type-assertion-expressions-delete-replacement-test",
"expectedResult": {
"changes": {
"type-assertion-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
10
]
}
},
"summary": "Deleted the 'b.(c.Dog)' type assertion statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Deleted the 'x.(z.Person)' type assertion statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
10
]
}
},
"summary": "Added the 'b.(c.Dog)' type assertion statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-assertion-expressions.go"
],
"patch": [
"diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
"index 56239fb..aa7c34c 100644",
"--- a/type-assertion-expressions.go",
"+++ b/type-assertion-expressions.go",
"@@ -1,3 +1,2 @@",
"-b.(c.Dog)",
"-x.(z.Person)",
" x.(z.Person)",
"+b.(c.Dog)"
],
"gitDir": "test/corpus/repos/go",
"shas": "596b57a4b9a75038c3f5594caa3561a52de5dc16..b9105039f8d9f039416e98ced5b9e80b8f7c7d40"
}
,{
"testCaseDescription": "go-type-assertion-expressions-delete-test",
"expectedResult": {
"changes": {
"type-assertion-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'x.(z.Person)' type assertion statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-assertion-expressions.go"
],
"patch": [
"diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
"index aa7c34c..093a081 100644",
"--- a/type-assertion-expressions.go",
"+++ b/type-assertion-expressions.go",
"@@ -1,2 +1 @@",
"-x.(z.Person)",
" b.(c.Dog)"
],
"gitDir": "test/corpus/repos/go",
"shas": "b9105039f8d9f039416e98ced5b9e80b8f7c7d40..868316791e7a76d17ffd45113d8b0a74886f8c90"
}
,{
"testCaseDescription": "go-type-assertion-expressions-delete-rest-test",
"expectedResult": {
"changes": {
"type-assertion-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
10
]
}
},
"summary": "Deleted the 'b.(c.Dog)' type assertion statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-assertion-expressions.go"
],
"patch": [
"diff --git a/type-assertion-expressions.go b/type-assertion-expressions.go",
"index 093a081..e69de29 100644",
"--- a/type-assertion-expressions.go",
"+++ b/type-assertion-expressions.go",
"@@ -1 +0,0 @@",
"-b.(c.Dog)"
],
"gitDir": "test/corpus/repos/go",
"shas": "868316791e7a76d17ffd45113d8b0a74886f8c90..5f76f266d80a0de28bb0535282f740664c37c11d"
}]

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,391 @@
[{
"testCaseDescription": "go-type-switch-statements-insert-test",
"expectedResult": {
"changes": {
"type-switch-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
6,
2
]
}
},
"summary": "Added the 'e' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-switch-statements.go"
],
"patch": [
"diff --git a/type-switch-statements.go b/type-switch-statements.go",
"index e69de29..f353f0b 100644",
"--- a/type-switch-statements.go",
"+++ b/type-switch-statements.go",
"@@ -0,0 +1,6 @@",
"+switch e.(type) {",
"+ case []Person:",
"+ a()",
"+ case *Dog:",
"+ break",
"+}"
],
"gitDir": "test/corpus/repos/go",
"shas": "d0a9400c6fb3a520721068d06591be6dba11ccee..a23aac7c9fe8328e6b75da50ba49937107ba5f13"
}
,{
"testCaseDescription": "go-type-switch-statements-replacement-insert-test",
"expectedResult": {
"changes": {
"type-switch-statements.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
6,
2
]
}
},
"summary": "Added the 'b' switch statement"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
12,
2
]
}
},
"summary": "Added the 'e' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-switch-statements.go"
],
"patch": [
"diff --git a/type-switch-statements.go b/type-switch-statements.go",
"index f353f0b..0c6eb84 100644",
"--- a/type-switch-statements.go",
"+++ b/type-switch-statements.go",
"@@ -1,3 +1,15 @@",
"+switch b.(type) {",
"+ case []Person:",
"+ a()",
"+ case *Dog:",
"+ break",
"+}",
"+switch e.(type) {",
"+ case []Person:",
"+ a()",
"+ case *Dog:",
"+ break",
"+}",
" switch e.(type) {",
" case []Person:",
" a()"
],
"gitDir": "test/corpus/repos/go",
"shas": "a23aac7c9fe8328e6b75da50ba49937107ba5f13..a4d2458afbff43bdfdc321aa60d79fd3a9c7dd12"
}
,{
"testCaseDescription": "go-type-switch-statements-delete-insert-test",
"expectedResult": {
"changes": {
"type-switch-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
8
],
"end": [
1,
9
]
},
{
"start": [
1,
8
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'e' identifier in the 'e' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-switch-statements.go"
],
"patch": [
"diff --git a/type-switch-statements.go b/type-switch-statements.go",
"index 0c6eb84..b373d6d 100644",
"--- a/type-switch-statements.go",
"+++ b/type-switch-statements.go",
"@@ -1,4 +1,4 @@",
"-switch b.(type) {",
"+switch e.(type) {",
" case []Person:",
" a()",
" case *Dog:"
],
"gitDir": "test/corpus/repos/go",
"shas": "a4d2458afbff43bdfdc321aa60d79fd3a9c7dd12..14d5cd3e4ef2783dc341266eb8c3d5b1aa4e38ec"
}
,{
"testCaseDescription": "go-type-switch-statements-replacement-test",
"expectedResult": {
"changes": {
"type-switch-statements.go": [
{
"span": {
"replace": [
{
"start": [
1,
8
],
"end": [
1,
9
]
},
{
"start": [
1,
8
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'e' identifier with the 'b' identifier in the 'b' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-switch-statements.go"
],
"patch": [
"diff --git a/type-switch-statements.go b/type-switch-statements.go",
"index b373d6d..0c6eb84 100644",
"--- a/type-switch-statements.go",
"+++ b/type-switch-statements.go",
"@@ -1,4 +1,4 @@",
"-switch e.(type) {",
"+switch b.(type) {",
" case []Person:",
" a()",
" case *Dog:"
],
"gitDir": "test/corpus/repos/go",
"shas": "14d5cd3e4ef2783dc341266eb8c3d5b1aa4e38ec..8e72f862af8f610979e789498e06f3c10ab247c0"
}
,{
"testCaseDescription": "go-type-switch-statements-delete-replacement-test",
"expectedResult": {
"changes": {
"type-switch-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
6,
2
]
}
},
"summary": "Deleted the 'b' switch statement"
},
{
"span": {
"delete": {
"start": [
7,
1
],
"end": [
12,
2
]
}
},
"summary": "Deleted the 'e' switch statement"
},
{
"span": {
"insert": {
"start": [
7,
1
],
"end": [
12,
2
]
}
},
"summary": "Added the 'b' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-switch-statements.go"
],
"patch": [
"diff --git a/type-switch-statements.go b/type-switch-statements.go",
"index 0c6eb84..64567d6 100644",
"--- a/type-switch-statements.go",
"+++ b/type-switch-statements.go",
"@@ -1,16 +1,10 @@",
"-switch b.(type) {",
"- case []Person:",
"- a()",
"- case *Dog:",
"- break",
"-}",
" switch e.(type) {",
" case []Person:",
" a()",
" case *Dog:",
" break",
" }",
"-switch e.(type) {",
"+switch b.(type) {",
" case []Person:",
" a()",
" case *Dog:"
],
"gitDir": "test/corpus/repos/go",
"shas": "8e72f862af8f610979e789498e06f3c10ab247c0..2da93d43c10edc4560f430395708b0a19deca7cf"
}
,{
"testCaseDescription": "go-type-switch-statements-delete-test",
"expectedResult": {
"changes": {
"type-switch-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
6,
2
]
}
},
"summary": "Deleted the 'e' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-switch-statements.go"
],
"patch": [
"diff --git a/type-switch-statements.go b/type-switch-statements.go",
"index 64567d6..047534a 100644",
"--- a/type-switch-statements.go",
"+++ b/type-switch-statements.go",
"@@ -1,9 +1,3 @@",
"-switch e.(type) {",
"- case []Person:",
"- a()",
"- case *Dog:",
"- break",
"-}",
" switch b.(type) {",
" case []Person:",
" a()"
],
"gitDir": "test/corpus/repos/go",
"shas": "2da93d43c10edc4560f430395708b0a19deca7cf..41efa01640ef05438abe68c7a166b50e79808f1c"
}
,{
"testCaseDescription": "go-type-switch-statements-delete-rest-test",
"expectedResult": {
"changes": {
"type-switch-statements.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
6,
2
]
}
},
"summary": "Deleted the 'b' switch statement"
}
]
},
"errors": {}
},
"filePaths": [
"type-switch-statements.go"
],
"patch": [
"diff --git a/type-switch-statements.go b/type-switch-statements.go",
"index 047534a..e69de29 100644",
"--- a/type-switch-statements.go",
"+++ b/type-switch-statements.go",
"@@ -1,6 +0,0 @@",
"-switch b.(type) {",
"- case []Person:",
"- a()",
"- case *Dog:",
"- break",
"-}"
],
"gitDir": "test/corpus/repos/go",
"shas": "41efa01640ef05438abe68c7a166b50e79808f1c..c02f9252b66f4d334e7e4d5cc2b56665c5d0b45f"
}]

View File

@ -0,0 +1,538 @@
[{
"testCaseDescription": "go-unary-expressions-insert-test",
"expectedResult": {
"changes": {
"unary-expressions.go": [
{
"span": {
"insert": {
"start": [
1,
4
],
"end": [
1,
5
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Added the 'identifier()' function call"
}
]
},
"errors": {}
},
"filePaths": [
"unary-expressions.go"
],
"patch": [
"diff --git a/unary-expressions.go b/unary-expressions.go",
"index e69de29..858c09a 100644",
"--- a/unary-expressions.go",
"+++ b/unary-expressions.go",
"@@ -0,0 +1,2 @@",
"+!<-a",
"+*foo()"
],
"gitDir": "test/corpus/repos/go",
"shas": "3403cd75b5874d1bc6c4c3c737525b7bd1271113..25caa48897bbba94e3ebd10df0cab8c1af27c26d"
}
,{
"testCaseDescription": "go-unary-expressions-replacement-insert-test",
"expectedResult": {
"changes": {
"unary-expressions.go": [
{
"span": {
"insert": {
"start": [
1,
4
],
"end": [
1,
5
]
}
},
"summary": "Added the 'b' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Added the 'identifier()' function call"
},
{
"span": {
"insert": {
"start": [
3,
4
],
"end": [
3,
5
]
}
},
"summary": "Added the 'a' identifier"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
7
]
}
},
"summary": "Added the 'identifier()' function call"
}
]
},
"errors": {}
},
"filePaths": [
"unary-expressions.go"
],
"patch": [
"diff --git a/unary-expressions.go b/unary-expressions.go",
"index 858c09a..0b42f98 100644",
"--- a/unary-expressions.go",
"+++ b/unary-expressions.go",
"@@ -1,2 +1,6 @@",
"+!<-b",
"+*bar()",
"+!<-a",
"+*foo()",
" !<-a",
" *foo()"
],
"gitDir": "test/corpus/repos/go",
"shas": "25caa48897bbba94e3ebd10df0cab8c1af27c26d..75a33545386bf76a55b02340bd336b00602e323e"
}
,{
"testCaseDescription": "go-unary-expressions-delete-insert-test",
"expectedResult": {
"changes": {
"unary-expressions.go": [
{
"span": {
"replace": [
{
"start": [
1,
4
],
"end": [
1,
5
]
},
{
"start": [
1,
4
],
"end": [
1,
5
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'a' identifier"
},
{
"span": {
"replace": [
{
"start": [
2,
2
],
"end": [
2,
5
]
},
{
"start": [
2,
2
],
"end": [
2,
5
]
}
]
},
"summary": "Replaced the 'bar' identifier with the 'foo' identifier in the identifier() function call"
}
]
},
"errors": {}
},
"filePaths": [
"unary-expressions.go"
],
"patch": [
"diff --git a/unary-expressions.go b/unary-expressions.go",
"index 0b42f98..25afb46 100644",
"--- a/unary-expressions.go",
"+++ b/unary-expressions.go",
"@@ -1,5 +1,5 @@",
"-!<-b",
"-*bar()",
"+!<-a",
"+*foo()",
" !<-a",
" *foo()",
" !<-a"
],
"gitDir": "test/corpus/repos/go",
"shas": "75a33545386bf76a55b02340bd336b00602e323e..32474c2bac0758793a5ff0f2139cab878545163a"
}
,{
"testCaseDescription": "go-unary-expressions-replacement-test",
"expectedResult": {
"changes": {
"unary-expressions.go": [
{
"span": {
"replace": [
{
"start": [
1,
4
],
"end": [
1,
5
]
},
{
"start": [
1,
4
],
"end": [
1,
5
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'b' identifier"
},
{
"span": {
"replace": [
{
"start": [
2,
2
],
"end": [
2,
5
]
},
{
"start": [
2,
2
],
"end": [
2,
5
]
}
]
},
"summary": "Replaced the 'foo' identifier with the 'bar' identifier in the identifier() function call"
}
]
},
"errors": {}
},
"filePaths": [
"unary-expressions.go"
],
"patch": [
"diff --git a/unary-expressions.go b/unary-expressions.go",
"index 25afb46..0b42f98 100644",
"--- a/unary-expressions.go",
"+++ b/unary-expressions.go",
"@@ -1,5 +1,5 @@",
"-!<-a",
"-*foo()",
"+!<-b",
"+*bar()",
" !<-a",
" *foo()",
" !<-a"
],
"gitDir": "test/corpus/repos/go",
"shas": "32474c2bac0758793a5ff0f2139cab878545163a..36454e266744a461ca2dd6934a061dc63a7c7a63"
}
,{
"testCaseDescription": "go-unary-expressions-delete-replacement-test",
"expectedResult": {
"changes": {
"unary-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
4
],
"end": [
1,
5
]
}
},
"summary": "Deleted the 'b' identifier"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'identifier()' function call"
},
{
"span": {
"delete": {
"start": [
3,
4
],
"end": [
3,
5
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
7
]
}
},
"summary": "Deleted the 'identifier()' function call"
},
{
"span": {
"insert": {
"start": [
3,
4
],
"end": [
3,
5
]
}
},
"summary": "Added the 'b' identifier"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
7
]
}
},
"summary": "Added the 'identifier()' function call"
}
]
},
"errors": {}
},
"filePaths": [
"unary-expressions.go"
],
"patch": [
"diff --git a/unary-expressions.go b/unary-expressions.go",
"index 0b42f98..812fb68 100644",
"--- a/unary-expressions.go",
"+++ b/unary-expressions.go",
"@@ -1,6 +1,4 @@",
"-!<-b",
"-*bar()",
"-!<-a",
"-*foo()",
" !<-a",
" *foo()",
"+!<-b",
"+*bar()"
],
"gitDir": "test/corpus/repos/go",
"shas": "36454e266744a461ca2dd6934a061dc63a7c7a63..2c0c14abd00ce4615876508894c87c15ad9f49e3"
}
,{
"testCaseDescription": "go-unary-expressions-delete-test",
"expectedResult": {
"changes": {
"unary-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
4
],
"end": [
1,
5
]
}
},
"summary": "Deleted the 'a' identifier"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'identifier()' function call"
}
]
},
"errors": {}
},
"filePaths": [
"unary-expressions.go"
],
"patch": [
"diff --git a/unary-expressions.go b/unary-expressions.go",
"index 812fb68..6da661d 100644",
"--- a/unary-expressions.go",
"+++ b/unary-expressions.go",
"@@ -1,4 +1,2 @@",
"-!<-a",
"-*foo()",
" !<-b",
" *bar()"
],
"gitDir": "test/corpus/repos/go",
"shas": "2c0c14abd00ce4615876508894c87c15ad9f49e3..742cb3cf4d2b7f71864c7795fd3307b8775538b3"
}
,{
"testCaseDescription": "go-unary-expressions-delete-rest-test",
"expectedResult": {
"changes": {
"unary-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
4
],
"end": [
1,
5
]
}
},
"summary": "Deleted the 'b' identifier"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'identifier()' function call"
}
]
},
"errors": {}
},
"filePaths": [
"unary-expressions.go"
],
"patch": [
"diff --git a/unary-expressions.go b/unary-expressions.go",
"index 6da661d..e69de29 100644",
"--- a/unary-expressions.go",
"+++ b/unary-expressions.go",
"@@ -1,2 +0,0 @@",
"-!<-b",
"-*bar()"
],
"gitDir": "test/corpus/repos/go",
"shas": "742cb3cf4d2b7f71864c7795fd3307b8775538b3..ecfd8333e0e37929a8029b0c03cec13c31e0f692"
}]

View File

@ -0,0 +1,712 @@
[{
"testCaseDescription": "go-var-declarations-with-no-expressions-insert-test",
"expectedResult": {
"changes": {
"var-declarations-with-no-expressions.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'zero' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
20
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
20
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-no-expressions.go"
],
"patch": [
"diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
"index e69de29..f156385 100644",
"--- a/var-declarations-with-no-expressions.go",
"+++ b/var-declarations-with-no-expressions.go",
"@@ -0,0 +1,2 @@",
"+var zero int",
"+var one, two uint64"
],
"gitDir": "test/corpus/repos/go",
"shas": "934c5da727053121abad016b81bcf0c4b922d4a9..cfdfa4a251864bbaee89d4be2a5ba16eba0f98f8"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-replacement-insert-test",
"expectedResult": {
"changes": {
"var-declarations-with-no-expressions.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
10
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
16
]
}
},
"summary": "Added the 'b' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
16
]
}
},
"summary": "Added the 'c' variable"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
13
]
}
},
"summary": "Added the 'zero' variable"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
20
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
20
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-no-expressions.go"
],
"patch": [
"diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
"index f156385..f696db9 100644",
"--- a/var-declarations-with-no-expressions.go",
"+++ b/var-declarations-with-no-expressions.go",
"@@ -1,2 +1,6 @@",
"+var a int",
"+var b, c uint64",
"+var zero int",
"+var one, two uint64",
" var zero int",
" var one, two uint64"
],
"gitDir": "test/corpus/repos/go",
"shas": "cfdfa4a251864bbaee89d4be2a5ba16eba0f98f8..4af9f85b09daf7d4a3067911981a2cae680b660d"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-delete-insert-test",
"expectedResult": {
"changes": {
"var-declarations-with-no-expressions.go": [
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
6
]
},
{
"start": [
1,
5
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'zero' identifier"
},
{
"span": {
"replace": [
{
"start": [
2,
5
],
"end": [
2,
6
]
},
{
"start": [
2,
5
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'one' identifier"
},
{
"span": {
"replace": [
{
"start": [
2,
8
],
"end": [
2,
9
]
},
{
"start": [
2,
10
],
"end": [
2,
13
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'two' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-no-expressions.go"
],
"patch": [
"diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
"index f696db9..e5e3183 100644",
"--- a/var-declarations-with-no-expressions.go",
"+++ b/var-declarations-with-no-expressions.go",
"@@ -1,5 +1,5 @@",
"-var a int",
"-var b, c uint64",
"+var zero int",
"+var one, two uint64",
" var zero int",
" var one, two uint64",
" var zero int"
],
"gitDir": "test/corpus/repos/go",
"shas": "4af9f85b09daf7d4a3067911981a2cae680b660d..f6f49bc348b0a2c0217811c9c49e27e46d4e6eb8"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-replacement-test",
"expectedResult": {
"changes": {
"var-declarations-with-no-expressions.go": [
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
9
]
},
{
"start": [
1,
5
],
"end": [
1,
6
]
}
]
},
"summary": "Replaced the 'zero' identifier with the 'a' identifier"
},
{
"span": {
"replace": [
{
"start": [
2,
5
],
"end": [
2,
8
]
},
{
"start": [
2,
5
],
"end": [
2,
6
]
}
]
},
"summary": "Replaced the 'one' identifier with the 'b' identifier"
},
{
"span": {
"replace": [
{
"start": [
2,
10
],
"end": [
2,
13
]
},
{
"start": [
2,
8
],
"end": [
2,
9
]
}
]
},
"summary": "Replaced the 'two' identifier with the 'c' identifier"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-no-expressions.go"
],
"patch": [
"diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
"index e5e3183..f696db9 100644",
"--- a/var-declarations-with-no-expressions.go",
"+++ b/var-declarations-with-no-expressions.go",
"@@ -1,5 +1,5 @@",
"-var zero int",
"-var one, two uint64",
"+var a int",
"+var b, c uint64",
" var zero int",
" var one, two uint64",
" var zero int"
],
"gitDir": "test/corpus/repos/go",
"shas": "f6f49bc348b0a2c0217811c9c49e27e46d4e6eb8..0f680098c076258ec348362f0f263dca661c617c"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-delete-replacement-test",
"expectedResult": {
"changes": {
"var-declarations-with-no-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
10
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
16
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
16
]
}
},
"summary": "Deleted the 'c' variable"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
13
]
}
},
"summary": "Deleted the 'zero' variable"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
20
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
20
]
}
},
"summary": "Deleted the 'two' variable"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
10
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
16
]
}
},
"summary": "Added the 'b' variable"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
16
]
}
},
"summary": "Added the 'c' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-no-expressions.go"
],
"patch": [
"diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
"index f696db9..137ee10 100644",
"--- a/var-declarations-with-no-expressions.go",
"+++ b/var-declarations-with-no-expressions.go",
"@@ -1,6 +1,4 @@",
"-var a int",
"-var b, c uint64",
"-var zero int",
"-var one, two uint64",
" var zero int",
" var one, two uint64",
"+var a int",
"+var b, c uint64"
],
"gitDir": "test/corpus/repos/go",
"shas": "0f680098c076258ec348362f0f263dca661c617c..b91d6b8dacfdb7c32799fd65a844cd65f999e6f5"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-delete-test",
"expectedResult": {
"changes": {
"var-declarations-with-no-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'zero' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
20
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
20
]
}
},
"summary": "Deleted the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-no-expressions.go"
],
"patch": [
"diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
"index 137ee10..443ec9e 100644",
"--- a/var-declarations-with-no-expressions.go",
"+++ b/var-declarations-with-no-expressions.go",
"@@ -1,4 +1,2 @@",
"-var zero int",
"-var one, two uint64",
" var a int",
" var b, c uint64"
],
"gitDir": "test/corpus/repos/go",
"shas": "b91d6b8dacfdb7c32799fd65a844cd65f999e6f5..7cbf36fbf74f4985dd2e5bc76f72956bd197f095"
}
,{
"testCaseDescription": "go-var-declarations-with-no-expressions-delete-rest-test",
"expectedResult": {
"changes": {
"var-declarations-with-no-expressions.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
10
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
16
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
16
]
}
},
"summary": "Deleted the 'c' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-no-expressions.go"
],
"patch": [
"diff --git a/var-declarations-with-no-expressions.go b/var-declarations-with-no-expressions.go",
"index 443ec9e..e69de29 100644",
"--- a/var-declarations-with-no-expressions.go",
"+++ b/var-declarations-with-no-expressions.go",
"@@ -1,2 +0,0 @@",
"-var a int",
"-var b, c uint64"
],
"gitDir": "test/corpus/repos/go",
"shas": "7cbf36fbf74f4985dd2e5bc76f72956bd197f095..87119afd9d847041735cf640ecc066ad2804a85f"
}]

View File

@ -0,0 +1,712 @@
[{
"testCaseDescription": "go-var-declarations-with-types-insert-test",
"expectedResult": {
"changes": {
"var-declarations-with-types.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
17
]
}
},
"summary": "Added the 'zero' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
27
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
27
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-types.go"
],
"patch": [
"diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
"index e69de29..7fa0f78 100644",
"--- a/var-declarations-with-types.go",
"+++ b/var-declarations-with-types.go",
"@@ -0,0 +1,2 @@",
"+var zero int = 0",
"+var one, two uint64 = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "4a563a4637d1f4bf47f9b6b9f47ca5acba82bfd2..bc75245000d830f0cc014c444f3a68bca289ed0a"
}
,{
"testCaseDescription": "go-var-declarations-with-types-replacement-insert-test",
"expectedResult": {
"changes": {
"var-declarations-with-types.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
14
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
2,
2
],
"end": [
2,
24
]
}
},
"summary": "Added the 'b' variable"
},
{
"span": {
"insert": {
"start": [
2,
2
],
"end": [
2,
24
]
}
},
"summary": "Added the 'c' variable"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
17
]
}
},
"summary": "Added the 'zero' variable"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
27
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
27
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-types.go"
],
"patch": [
"diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
"index 7fa0f78..bf0a293 100644",
"--- a/var-declarations-with-types.go",
"+++ b/var-declarations-with-types.go",
"@@ -1,2 +1,6 @@",
"+var a int = 0",
"+ var b, c uint64 = 1, 2",
"+var zero int = 0",
"+var one, two uint64 = 1, 2",
" var zero int = 0",
" var one, two uint64 = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "bc75245000d830f0cc014c444f3a68bca289ed0a..a9f4cd4a5019134807cf1f82ff1b74b7e90bdc50"
}
,{
"testCaseDescription": "go-var-declarations-with-types-delete-insert-test",
"expectedResult": {
"changes": {
"var-declarations-with-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
6
]
},
{
"start": [
1,
5
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
2,
6
],
"end": [
2,
7
]
},
{
"start": [
2,
5
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'one' identifier in the one variable"
},
{
"span": {
"replace": [
{
"start": [
2,
9
],
"end": [
2,
10
]
},
{
"start": [
2,
10
],
"end": [
2,
13
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'two' identifier in the two variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-types.go"
],
"patch": [
"diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
"index bf0a293..cba22b9 100644",
"--- a/var-declarations-with-types.go",
"+++ b/var-declarations-with-types.go",
"@@ -1,5 +1,5 @@",
"-var a int = 0",
"- var b, c uint64 = 1, 2",
"+var zero int = 0",
"+var one, two uint64 = 1, 2",
" var zero int = 0",
" var one, two uint64 = 1, 2",
" var zero int = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "a9f4cd4a5019134807cf1f82ff1b74b7e90bdc50..fddf3c784f6c2d1a53c3e3c6de720822d0e90f2a"
}
,{
"testCaseDescription": "go-var-declarations-with-types-replacement-test",
"expectedResult": {
"changes": {
"var-declarations-with-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
9
]
},
{
"start": [
1,
5
],
"end": [
1,
6
]
}
]
},
"summary": "Replaced the 'zero' identifier with the 'a' identifier in the a variable"
},
{
"span": {
"replace": [
{
"start": [
2,
5
],
"end": [
2,
8
]
},
{
"start": [
2,
6
],
"end": [
2,
7
]
}
]
},
"summary": "Replaced the 'one' identifier with the 'b' identifier in the b variable"
},
{
"span": {
"replace": [
{
"start": [
2,
10
],
"end": [
2,
13
]
},
{
"start": [
2,
9
],
"end": [
2,
10
]
}
]
},
"summary": "Replaced the 'two' identifier with the 'c' identifier in the c variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-types.go"
],
"patch": [
"diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
"index cba22b9..bf0a293 100644",
"--- a/var-declarations-with-types.go",
"+++ b/var-declarations-with-types.go",
"@@ -1,5 +1,5 @@",
"-var zero int = 0",
"-var one, two uint64 = 1, 2",
"+var a int = 0",
"+ var b, c uint64 = 1, 2",
" var zero int = 0",
" var one, two uint64 = 1, 2",
" var zero int = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "fddf3c784f6c2d1a53c3e3c6de720822d0e90f2a..873d8bbf42f8e863405179f45fd270a05f58baaf"
}
,{
"testCaseDescription": "go-var-declarations-with-types-delete-replacement-test",
"expectedResult": {
"changes": {
"var-declarations-with-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
14
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
2,
2
],
"end": [
2,
24
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"delete": {
"start": [
2,
2
],
"end": [
2,
24
]
}
},
"summary": "Deleted the 'c' variable"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
17
]
}
},
"summary": "Deleted the 'zero' variable"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
27
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
27
]
}
},
"summary": "Deleted the 'two' variable"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
14
]
}
},
"summary": "Added the 'a' variable"
},
{
"span": {
"insert": {
"start": [
4,
2
],
"end": [
4,
24
]
}
},
"summary": "Added the 'b' variable"
},
{
"span": {
"insert": {
"start": [
4,
2
],
"end": [
4,
24
]
}
},
"summary": "Added the 'c' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-types.go"
],
"patch": [
"diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
"index bf0a293..bd11fef 100644",
"--- a/var-declarations-with-types.go",
"+++ b/var-declarations-with-types.go",
"@@ -1,6 +1,4 @@",
"-var a int = 0",
"- var b, c uint64 = 1, 2",
"-var zero int = 0",
"-var one, two uint64 = 1, 2",
" var zero int = 0",
" var one, two uint64 = 1, 2",
"+var a int = 0",
"+ var b, c uint64 = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "873d8bbf42f8e863405179f45fd270a05f58baaf..5d08dfef677b002958c94324b95ecc118be2c1de"
}
,{
"testCaseDescription": "go-var-declarations-with-types-delete-test",
"expectedResult": {
"changes": {
"var-declarations-with-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
17
]
}
},
"summary": "Deleted the 'zero' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
27
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
27
]
}
},
"summary": "Deleted the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-types.go"
],
"patch": [
"diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
"index bd11fef..6e0b7e7 100644",
"--- a/var-declarations-with-types.go",
"+++ b/var-declarations-with-types.go",
"@@ -1,4 +1,2 @@",
"-var zero int = 0",
"-var one, two uint64 = 1, 2",
" var a int = 0",
" var b, c uint64 = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "5d08dfef677b002958c94324b95ecc118be2c1de..771cd9d7d33a80c0327a1ecf0aea69a1c0e8dd0e"
}
,{
"testCaseDescription": "go-var-declarations-with-types-delete-rest-test",
"expectedResult": {
"changes": {
"var-declarations-with-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
14
]
}
},
"summary": "Deleted the 'a' variable"
},
{
"span": {
"delete": {
"start": [
2,
2
],
"end": [
2,
24
]
}
},
"summary": "Deleted the 'b' variable"
},
{
"span": {
"delete": {
"start": [
2,
2
],
"end": [
2,
24
]
}
},
"summary": "Deleted the 'c' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-with-types.go"
],
"patch": [
"diff --git a/var-declarations-with-types.go b/var-declarations-with-types.go",
"index 6e0b7e7..e69de29 100644",
"--- a/var-declarations-with-types.go",
"+++ b/var-declarations-with-types.go",
"@@ -1,2 +0,0 @@",
"-var a int = 0",
"- var b, c uint64 = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "771cd9d7d33a80c0327a1ecf0aea69a1c0e8dd0e..934c5da727053121abad016b81bcf0c4b922d4a9"
}]

View File

@ -0,0 +1,491 @@
[{
"testCaseDescription": "go-var-declarations-without-types-insert-test",
"expectedResult": {
"changes": {
"var-declarations-without-types.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'zero' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-without-types.go"
],
"patch": [
"diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
"index e69de29..8c7993a 100644",
"--- a/var-declarations-without-types.go",
"+++ b/var-declarations-without-types.go",
"@@ -0,0 +1 @@",
"+var zero = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "5352a466a13a8f3f02aa66c9a40c94ce75e0e613..9d6d497e69f31aa9df97506de0154a1e61f4d9e4"
}
,{
"testCaseDescription": "go-var-declarations-without-types-replacement-insert-test",
"expectedResult": {
"changes": {
"var-declarations-without-types.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Added the 'two' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Added the 'zero' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-without-types.go"
],
"patch": [
"diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
"index 8c7993a..80fe8ba 100644",
"--- a/var-declarations-without-types.go",
"+++ b/var-declarations-without-types.go",
"@@ -1 +1,3 @@",
"+var one, two = 1, 2",
"+var zero = 0",
" var zero = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "9d6d497e69f31aa9df97506de0154a1e61f4d9e4..ea6ae7e686e42ad7362086e079769670ea10936f"
}
,{
"testCaseDescription": "go-var-declarations-without-types-delete-insert-test",
"expectedResult": {
"changes": {
"var-declarations-without-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
8
]
},
{
"start": [
1,
5
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'one' identifier with the 'zero' identifier in the zero variable"
},
{
"span": {
"replace": [
{
"start": [
1,
16
],
"end": [
1,
17
]
},
{
"start": [
1,
12
],
"end": [
1,
13
]
}
]
},
"summary": "Replaced '1' with '0' in the zero variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Deleted the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-without-types.go"
],
"patch": [
"diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
"index 80fe8ba..c4df5f9 100644",
"--- a/var-declarations-without-types.go",
"+++ b/var-declarations-without-types.go",
"@@ -1,3 +1,3 @@",
"-var one, two = 1, 2",
"+var zero = 0",
" var zero = 0",
" var zero = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "ea6ae7e686e42ad7362086e079769670ea10936f..1d7f81f8dedc3d055e53d2e148bc244fd223ba95"
}
,{
"testCaseDescription": "go-var-declarations-without-types-replacement-test",
"expectedResult": {
"changes": {
"var-declarations-without-types.go": [
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
9
]
},
{
"start": [
1,
5
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced the 'zero' identifier with the 'one' identifier in the one variable"
},
{
"span": {
"replace": [
{
"start": [
1,
12
],
"end": [
1,
13
]
},
{
"start": [
1,
16
],
"end": [
1,
17
]
}
]
},
"summary": "Replaced '0' with '1' in the one variable"
},
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-without-types.go"
],
"patch": [
"diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
"index c4df5f9..80fe8ba 100644",
"--- a/var-declarations-without-types.go",
"+++ b/var-declarations-without-types.go",
"@@ -1,3 +1,3 @@",
"-var zero = 0",
"+var one, two = 1, 2",
" var zero = 0",
" var zero = 0"
],
"gitDir": "test/corpus/repos/go",
"shas": "1d7f81f8dedc3d055e53d2e148bc244fd223ba95..9b622b9e582499d0adaf52cec95b949194138ebe"
}
,{
"testCaseDescription": "go-var-declarations-without-types-delete-replacement-test",
"expectedResult": {
"changes": {
"var-declarations-without-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Deleted the 'two' variable"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Deleted the 'zero' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
20
]
}
},
"summary": "Added the 'one' variable"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
20
]
}
},
"summary": "Added the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-without-types.go"
],
"patch": [
"diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
"index 80fe8ba..0d0b543 100644",
"--- a/var-declarations-without-types.go",
"+++ b/var-declarations-without-types.go",
"@@ -1,3 +1,2 @@",
"-var one, two = 1, 2",
"-var zero = 0",
" var zero = 0",
"+var one, two = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "9b622b9e582499d0adaf52cec95b949194138ebe..34a7c384276ec72530b60e7c7b97e7cd26bf8292"
}
,{
"testCaseDescription": "go-var-declarations-without-types-delete-test",
"expectedResult": {
"changes": {
"var-declarations-without-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'zero' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-without-types.go"
],
"patch": [
"diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
"index 0d0b543..c4a6ab5 100644",
"--- a/var-declarations-without-types.go",
"+++ b/var-declarations-without-types.go",
"@@ -1,2 +1 @@",
"-var zero = 0",
" var one, two = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "34a7c384276ec72530b60e7c7b97e7cd26bf8292..8ef765a217c5233472add0c29d15341458c4b793"
}
,{
"testCaseDescription": "go-var-declarations-without-types-delete-rest-test",
"expectedResult": {
"changes": {
"var-declarations-without-types.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Deleted the 'one' variable"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Deleted the 'two' variable"
}
]
},
"errors": {}
},
"filePaths": [
"var-declarations-without-types.go"
],
"patch": [
"diff --git a/var-declarations-without-types.go b/var-declarations-without-types.go",
"index c4a6ab5..e69de29 100644",
"--- a/var-declarations-without-types.go",
"+++ b/var-declarations-without-types.go",
"@@ -1 +0,0 @@",
"-var one, two = 1, 2"
],
"gitDir": "test/corpus/repos/go",
"shas": "8ef765a217c5233472add0c29d15341458c4b793..4a563a4637d1f4bf47f9b6b9f47ca5acba82bfd2"
}]

View File

@ -0,0 +1,727 @@
[{
"testCaseDescription": "go-variadic-function-declarations-insert-test",
"expectedResult": {
"changes": {
"variadic-function-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Added the 'f1' function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Added the 'f2' function"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
23
]
}
},
"summary": "Added the 'f3' function"
}
]
},
"errors": {}
},
"filePaths": [
"variadic-function-declarations.go"
],
"patch": [
"diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
"index e69de29..e9d461f 100644",
"--- a/variadic-function-declarations.go",
"+++ b/variadic-function-declarations.go",
"@@ -0,0 +1,3 @@",
"+func f1(a ...*int) {}",
"+func f2(...int) {}",
"+func f3(a, ...bool) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "7e354b885fbffacfc60e09f0bd093cf0e6c38e3f..cf75422bf72ec2da7ad9d55e998b56b8b381a5e0"
}
,{
"testCaseDescription": "go-variadic-function-declarations-replacement-insert-test",
"expectedResult": {
"changes": {
"variadic-function-declarations.go": [
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Added the 'g1' function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Added the 'g2' function"
},
{
"span": {
"insert": {
"start": [
3,
1
],
"end": [
3,
23
]
}
},
"summary": "Added the 'g3' function"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
22
]
}
},
"summary": "Added the 'f1' function"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
19
]
}
},
"summary": "Added the 'f2' function"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
23
]
}
},
"summary": "Added the 'f3' function"
}
]
},
"errors": {}
},
"filePaths": [
"variadic-function-declarations.go"
],
"patch": [
"diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
"index e9d461f..1e4f816 100644",
"--- a/variadic-function-declarations.go",
"+++ b/variadic-function-declarations.go",
"@@ -1,3 +1,9 @@",
"+func g1(a ...*int) {}",
"+func g2(...int) {}",
"+func g3(a, ...bool) {}",
"+func f1(a ...*int) {}",
"+func f2(...int) {}",
"+func f3(a, ...bool) {}",
" func f1(a ...*int) {}",
" func f2(...int) {}",
" func f3(a, ...bool) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "cf75422bf72ec2da7ad9d55e998b56b8b381a5e0..380e9576d3e0f9f57e2e458a585408d7267eefa3"
}
,{
"testCaseDescription": "go-variadic-function-declarations-delete-insert-test",
"expectedResult": {
"changes": {
"variadic-function-declarations.go": [
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
8
]
},
{
"start": [
1,
6
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced the 'g1' identifier with the 'f1' identifier in the f1 function"
},
{
"span": {
"replace": [
{
"start": [
2,
6
],
"end": [
2,
8
]
},
{
"start": [
2,
6
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the 'g2' identifier with the 'f2' identifier in the f2 function"
},
{
"span": {
"replace": [
{
"start": [
3,
6
],
"end": [
3,
8
]
},
{
"start": [
3,
6
],
"end": [
3,
8
]
}
]
},
"summary": "Replaced the 'g3' identifier with the 'f3' identifier in the f3 function"
}
]
},
"errors": {}
},
"filePaths": [
"variadic-function-declarations.go"
],
"patch": [
"diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
"index 1e4f816..3198ec6 100644",
"--- a/variadic-function-declarations.go",
"+++ b/variadic-function-declarations.go",
"@@ -1,6 +1,6 @@",
"-func g1(a ...*int) {}",
"-func g2(...int) {}",
"-func g3(a, ...bool) {}",
"+func f1(a ...*int) {}",
"+func f2(...int) {}",
"+func f3(a, ...bool) {}",
" func f1(a ...*int) {}",
" func f2(...int) {}",
" func f3(a, ...bool) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "380e9576d3e0f9f57e2e458a585408d7267eefa3..23d80f0e25ec808901f39ee0c7fccb2c2cf821d2"
}
,{
"testCaseDescription": "go-variadic-function-declarations-replacement-test",
"expectedResult": {
"changes": {
"variadic-function-declarations.go": [
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
8
]
},
{
"start": [
1,
6
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced the 'f1' identifier with the 'g1' identifier in the g1 function"
},
{
"span": {
"replace": [
{
"start": [
2,
6
],
"end": [
2,
8
]
},
{
"start": [
2,
6
],
"end": [
2,
8
]
}
]
},
"summary": "Replaced the 'f2' identifier with the 'g2' identifier in the g2 function"
},
{
"span": {
"replace": [
{
"start": [
3,
6
],
"end": [
3,
8
]
},
{
"start": [
3,
6
],
"end": [
3,
8
]
}
]
},
"summary": "Replaced the 'f3' identifier with the 'g3' identifier in the g3 function"
}
]
},
"errors": {}
},
"filePaths": [
"variadic-function-declarations.go"
],
"patch": [
"diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
"index 3198ec6..1e4f816 100644",
"--- a/variadic-function-declarations.go",
"+++ b/variadic-function-declarations.go",
"@@ -1,6 +1,6 @@",
"-func f1(a ...*int) {}",
"-func f2(...int) {}",
"-func f3(a, ...bool) {}",
"+func g1(a ...*int) {}",
"+func g2(...int) {}",
"+func g3(a, ...bool) {}",
" func f1(a ...*int) {}",
" func f2(...int) {}",
" func f3(a, ...bool) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "23d80f0e25ec808901f39ee0c7fccb2c2cf821d2..37463058446cc3b2dca8f4b3e5b31cf0a71ad47f"
}
,{
"testCaseDescription": "go-variadic-function-declarations-delete-replacement-test",
"expectedResult": {
"changes": {
"variadic-function-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Deleted the 'g1' function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Deleted the 'g2' function"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
23
]
}
},
"summary": "Deleted the 'g3' function"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
22
]
}
},
"summary": "Deleted the 'f1' function"
},
{
"span": {
"delete": {
"start": [
5,
1
],
"end": [
5,
19
]
}
},
"summary": "Deleted the 'f2' function"
},
{
"span": {
"delete": {
"start": [
6,
1
],
"end": [
6,
23
]
}
},
"summary": "Deleted the 'f3' function"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
22
]
}
},
"summary": "Added the 'g1' function"
},
{
"span": {
"insert": {
"start": [
5,
1
],
"end": [
5,
19
]
}
},
"summary": "Added the 'g2' function"
},
{
"span": {
"insert": {
"start": [
6,
1
],
"end": [
6,
23
]
}
},
"summary": "Added the 'g3' function"
}
]
},
"errors": {}
},
"filePaths": [
"variadic-function-declarations.go"
],
"patch": [
"diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
"index 1e4f816..99d1e54 100644",
"--- a/variadic-function-declarations.go",
"+++ b/variadic-function-declarations.go",
"@@ -1,9 +1,6 @@",
"-func g1(a ...*int) {}",
"-func g2(...int) {}",
"-func g3(a, ...bool) {}",
"-func f1(a ...*int) {}",
"-func f2(...int) {}",
"-func f3(a, ...bool) {}",
" func f1(a ...*int) {}",
" func f2(...int) {}",
" func f3(a, ...bool) {}",
"+func g1(a ...*int) {}",
"+func g2(...int) {}",
"+func g3(a, ...bool) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "37463058446cc3b2dca8f4b3e5b31cf0a71ad47f..634ee9c283be48136a0f3c06b934109faa47d05e"
}
,{
"testCaseDescription": "go-variadic-function-declarations-delete-test",
"expectedResult": {
"changes": {
"variadic-function-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Deleted the 'f1' function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Deleted the 'f2' function"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
23
]
}
},
"summary": "Deleted the 'f3' function"
}
]
},
"errors": {}
},
"filePaths": [
"variadic-function-declarations.go"
],
"patch": [
"diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
"index 99d1e54..4a0a10b 100644",
"--- a/variadic-function-declarations.go",
"+++ b/variadic-function-declarations.go",
"@@ -1,6 +1,3 @@",
"-func f1(a ...*int) {}",
"-func f2(...int) {}",
"-func f3(a, ...bool) {}",
" func g1(a ...*int) {}",
" func g2(...int) {}",
" func g3(a, ...bool) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "634ee9c283be48136a0f3c06b934109faa47d05e..89489f7609fbf07766acd9bbaef1b561e3b9ec44"
}
,{
"testCaseDescription": "go-variadic-function-declarations-delete-rest-test",
"expectedResult": {
"changes": {
"variadic-function-declarations.go": [
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Deleted the 'g1' function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Deleted the 'g2' function"
},
{
"span": {
"delete": {
"start": [
3,
1
],
"end": [
3,
23
]
}
},
"summary": "Deleted the 'g3' function"
}
]
},
"errors": {}
},
"filePaths": [
"variadic-function-declarations.go"
],
"patch": [
"diff --git a/variadic-function-declarations.go b/variadic-function-declarations.go",
"index 4a0a10b..e69de29 100644",
"--- a/variadic-function-declarations.go",
"+++ b/variadic-function-declarations.go",
"@@ -1,3 +0,0 @@",
"-func g1(a ...*int) {}",
"-func g2(...int) {}",
"-func g3(a, ...bool) {}"
],
"gitDir": "test/corpus/repos/go",
"shas": "89489f7609fbf07766acd9bbaef1b561e3b9ec44..22e1c316ab762143194da47885ee3153ecfeda38"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "c3ba4a1505773022c8c9750803b2f78c821f80a1",
"patch": [
"diff --git a/anonymous-function.js b/anonymous-function.js",
"index e69de29..b592868 100644",
"--- a/anonymous-function.js",
"+++ b/anonymous-function.js",
"@@ -0,0 +1 @@",
"+function(a,b) { return a + b; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b5bdaebe1a62c35afbab412c48b69be687db7d09"
"shas": "5f4dfa791577127cebc7f5fa8c7d94b7427980f3..2e9eda4d95ac6cbdd16de3ad1464523de63ffb44"
}
,{
"testCaseDescription": "javascript-anonymous-function-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "b5bdaebe1a62c35afbab412c48b69be687db7d09",
"patch": [
"diff --git a/anonymous-function.js b/anonymous-function.js",
"index b592868..e1de356 100644",
"--- a/anonymous-function.js",
"+++ b/anonymous-function.js",
"@@ -1 +1,3 @@",
"+function(b,c) { return b * c; }",
"+function(a,b) { return a + b; }",
" function(a,b) { return a + b; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "79300c371f63ca7d92884cf2e4cb676518313a20"
"shas": "2e9eda4d95ac6cbdd16de3ad1464523de63ffb44..d6d789dd70b74b099621405aaab5cbb25e1a47eb"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-insert-test",
@ -195,9 +211,19 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "79300c371f63ca7d92884cf2e4cb676518313a20",
"patch": [
"diff --git a/anonymous-function.js b/anonymous-function.js",
"index e1de356..4ca0d4c 100644",
"--- a/anonymous-function.js",
"+++ b/anonymous-function.js",
"@@ -1,3 +1,3 @@",
"-function(b,c) { return b * c; }",
"+function(a,b) { return a + b; }",
" function(a,b) { return a + b; }",
" function(a,b) { return a + b; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "016507d5f7e94b37702891fc7b0d62b850b6e225"
"shas": "d6d789dd70b74b099621405aaab5cbb25e1a47eb..d40be86ea2ce078c6a426ce0a8c252a71892113a"
}
,{
"testCaseDescription": "javascript-anonymous-function-replacement-test",
@ -319,9 +345,19 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "016507d5f7e94b37702891fc7b0d62b850b6e225",
"patch": [
"diff --git a/anonymous-function.js b/anonymous-function.js",
"index 4ca0d4c..e1de356 100644",
"--- a/anonymous-function.js",
"+++ b/anonymous-function.js",
"@@ -1,3 +1,3 @@",
"-function(a,b) { return a + b; }",
"+function(b,c) { return b * c; }",
" function(a,b) { return a + b; }",
" function(a,b) { return a + b; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "3fb4175329fcd15fec0bbc2fc1bf9180bdf4fbcd"
"shas": "d40be86ea2ce078c6a426ce0a8c252a71892113a..fbe8b2947cb17ec793516f3368dd2f787bccfe66"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-replacement-test",
@ -380,9 +416,19 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "3fb4175329fcd15fec0bbc2fc1bf9180bdf4fbcd",
"patch": [
"diff --git a/anonymous-function.js b/anonymous-function.js",
"index e1de356..afdaccf 100644",
"--- a/anonymous-function.js",
"+++ b/anonymous-function.js",
"@@ -1,3 +1,2 @@",
"-function(b,c) { return b * c; }",
"-function(a,b) { return a + b; }",
" function(a,b) { return a + b; }",
"+function(b,c) { return b * c; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "690cd36fd94756b8e231d0e5134619fe533b1a87"
"shas": "fbe8b2947cb17ec793516f3368dd2f787bccfe66..260e74caf2632a2de525e1341d76ed31cc8cf2bf"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-test",
@ -411,9 +457,17 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "690cd36fd94756b8e231d0e5134619fe533b1a87",
"patch": [
"diff --git a/anonymous-function.js b/anonymous-function.js",
"index afdaccf..9f1856f 100644",
"--- a/anonymous-function.js",
"+++ b/anonymous-function.js",
"@@ -1,2 +1 @@",
"-function(a,b) { return a + b; }",
" function(b,c) { return b * c; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9b5d868b31faea679ddb9fe61b59042398eb187a"
"shas": "260e74caf2632a2de525e1341d76ed31cc8cf2bf..f425fbe0cbbd72279ea1a69e34baa8e341700a09"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-rest-test",
@ -442,7 +496,14 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "9b5d868b31faea679ddb9fe61b59042398eb187a",
"patch": [
"diff --git a/anonymous-function.js b/anonymous-function.js",
"index 9f1856f..e69de29 100644",
"--- a/anonymous-function.js",
"+++ b/anonymous-function.js",
"@@ -1 +0,0 @@",
"-function(b,c) { return b * c; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9fd0f7aee44dbf83b9a380bad5755081b4246e77"
"shas": "f425fbe0cbbd72279ea1a69e34baa8e341700a09..2a5f85a471c9c83f2e835139afa5eb7bfecd546a"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "9fd0f7aee44dbf83b9a380bad5755081b4246e77",
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
"index e69de29..4a26ae8 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -0,0 +1 @@",
"+function() { return 'hi'; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "3f71749ad94ee55259b0185c358235d8ac903467"
"shas": "2a5f85a471c9c83f2e835139afa5eb7bfecd546a..a2527ab39dbaa7651e66e24f3d143d11060841f6"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "3f71749ad94ee55259b0185c358235d8ac903467",
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
"index 4a26ae8..c31dd4b 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1 +1,3 @@",
"+function() { return 'hello'; }",
"+function() { return 'hi'; }",
" function() { return 'hi'; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "0863179c63f1167cdfb18c909a4085cc496937f6"
"shas": "a2527ab39dbaa7651e66e24f3d143d11060841f6..4b3321e8a707ad91af6735319257f7f68fb593b7"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test",
@ -114,9 +130,19 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "0863179c63f1167cdfb18c909a4085cc496937f6",
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
"index c31dd4b..6b1efa4 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1,3 +1,3 @@",
"-function() { return 'hello'; }",
"+function() { return 'hi'; }",
" function() { return 'hi'; }",
" function() { return 'hi'; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "694e7e4dbf661db0da87a68db68975fe34fdba3f"
"shas": "4b3321e8a707ad91af6735319257f7f68fb593b7..a01626612654464812b9cedaad745f686edc8138"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test",
@ -157,9 +183,19 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "694e7e4dbf661db0da87a68db68975fe34fdba3f",
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
"index 6b1efa4..c31dd4b 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1,3 +1,3 @@",
"-function() { return 'hi'; }",
"+function() { return 'hello'; }",
" function() { return 'hi'; }",
" function() { return 'hi'; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "353eeb99fc286d0683f1d698a8f6212ce4699acd"
"shas": "a01626612654464812b9cedaad745f686edc8138..d640dfcedbbda8708bb8c679b2b96460e63e8e53"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test",
@ -218,9 +254,19 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "353eeb99fc286d0683f1d698a8f6212ce4699acd",
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
"index c31dd4b..b8e05c0 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1,3 +1,2 @@",
"-function() { return 'hello'; }",
"-function() { return 'hi'; }",
" function() { return 'hi'; }",
"+function() { return 'hello'; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9862380b35add3763257a9f558bf4ff02427d9cf"
"shas": "d640dfcedbbda8708bb8c679b2b96460e63e8e53..f1436a17d64c050a7d6aa15fe0876ce3fc4176f0"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-test",
@ -249,9 +295,17 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "9862380b35add3763257a9f558bf4ff02427d9cf",
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
"index b8e05c0..ce1ef83 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1,2 +1 @@",
"-function() { return 'hi'; }",
" function() { return 'hello'; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "e42905606a9100ef0e06cb728b265e6d772e9a9f"
"shas": "f1436a17d64c050a7d6aa15fe0876ce3fc4176f0..1bd2372f874ec3588d5510b5c7fa50c378b5e665"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test",
@ -280,7 +334,14 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "e42905606a9100ef0e06cb728b265e6d772e9a9f",
"patch": [
"diff --git a/anonymous-parameterless-function.js b/anonymous-parameterless-function.js",
"index ce1ef83..e69de29 100644",
"--- a/anonymous-parameterless-function.js",
"+++ b/anonymous-parameterless-function.js",
"@@ -1 +0,0 @@",
"-function() { return 'hello'; }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "8662f58f1d7ce21fddcefecae990742a5d1398dc"
"shas": "1bd2372f874ec3588d5510b5c7fa50c378b5e665..e66b1b20abc596d2b560eaa80f1749c79816f9ff"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"array.js"
],
"sha1": "9ccab273233837d842e68ec909416aab24ff359a",
"patch": [
"diff --git a/array.js b/array.js",
"index e69de29..3335582 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -0,0 +1 @@",
"+[ \"item1\" ];"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b653c66def8445f3ba4880fee2c049196d273774"
"shas": "654a538b26c9b4c8637e6c2e4cd497c93e690310..cbf013688399920af101ea056e9fba5ecba0601d"
}
,{
"testCaseDescription": "javascript-array-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"array.js"
],
"sha1": "b653c66def8445f3ba4880fee2c049196d273774",
"patch": [
"diff --git a/array.js b/array.js",
"index 3335582..cf37d7c 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1 +1,3 @@",
"+[ \"item1\", \"item2\" ];",
"+[ \"item1\" ];",
" [ \"item1\" ];"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "c055d2c11306c9f9cbb2ed0d9f0b638b953f7b4a"
"shas": "cbf013688399920af101ea056e9fba5ecba0601d..87e3b9ed3c5f26c596ad2b5da90359174c84f53c"
}
,{
"testCaseDescription": "javascript-array-delete-insert-test",
@ -102,9 +118,19 @@
"filePaths": [
"array.js"
],
"sha1": "c055d2c11306c9f9cbb2ed0d9f0b638b953f7b4a",
"patch": [
"diff --git a/array.js b/array.js",
"index cf37d7c..c2cb17f 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1,3 +1,3 @@",
"-[ \"item1\", \"item2\" ];",
"+[ \"item1\" ];",
" [ \"item1\" ];",
" [ \"item1\" ];"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "074894088cf9d55ae3bcdbb3a8e4270b8d2a0c26"
"shas": "87e3b9ed3c5f26c596ad2b5da90359174c84f53c..ea49177e8ff82b772f7347682975cb1fa5e7b012"
}
,{
"testCaseDescription": "javascript-array-replacement-test",
@ -133,9 +159,19 @@
"filePaths": [
"array.js"
],
"sha1": "074894088cf9d55ae3bcdbb3a8e4270b8d2a0c26",
"patch": [
"diff --git a/array.js b/array.js",
"index c2cb17f..cf37d7c 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1,3 +1,3 @@",
"-[ \"item1\" ];",
"+[ \"item1\", \"item2\" ];",
" [ \"item1\" ];",
" [ \"item1\" ];"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "7e646e80e9fabf33c78eca4122ac60e146b52423"
"shas": "ea49177e8ff82b772f7347682975cb1fa5e7b012..1e28fd793a6ab61ed59b28d8ee56b55be7ad79ec"
}
,{
"testCaseDescription": "javascript-array-delete-replacement-test",
@ -194,9 +230,19 @@
"filePaths": [
"array.js"
],
"sha1": "7e646e80e9fabf33c78eca4122ac60e146b52423",
"patch": [
"diff --git a/array.js b/array.js",
"index cf37d7c..a4d92b8 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1,3 +1,2 @@",
"-[ \"item1\", \"item2\" ];",
"-[ \"item1\" ];",
" [ \"item1\" ];",
"+[ \"item1\", \"item2\" ];"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "c61cc49cb2088ca7e12614a4b31e181f5a0e97d6"
"shas": "1e28fd793a6ab61ed59b28d8ee56b55be7ad79ec..fdc62b5a013932e082ba61a576b8fb54cd1d0791"
}
,{
"testCaseDescription": "javascript-array-delete-test",
@ -225,9 +271,17 @@
"filePaths": [
"array.js"
],
"sha1": "c61cc49cb2088ca7e12614a4b31e181f5a0e97d6",
"patch": [
"diff --git a/array.js b/array.js",
"index a4d92b8..7f2f50e 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1,2 +1 @@",
"-[ \"item1\" ];",
" [ \"item1\", \"item2\" ];"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9601453a391957f917ee112f1e6abce225b21bac"
"shas": "fdc62b5a013932e082ba61a576b8fb54cd1d0791..9e91959fe3d3ec022474f242a8456b900fdfd8d2"
}
,{
"testCaseDescription": "javascript-array-delete-rest-test",
@ -256,7 +310,14 @@
"filePaths": [
"array.js"
],
"sha1": "9601453a391957f917ee112f1e6abce225b21bac",
"patch": [
"diff --git a/array.js b/array.js",
"index 7f2f50e..e69de29 100644",
"--- a/array.js",
"+++ b/array.js",
"@@ -1 +0,0 @@",
"-[ \"item1\", \"item2\" ];"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "e1f7c5a495d4e15d24ac325f6dec565f21f021e8"
"shas": "9e91959fe3d3ec022474f242a8456b900fdfd8d2..0bdf412036a9a6aea51108a20404c37541fffcfb"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "1a65f6b31571ca180a7067af4efe0b804b5bd17f",
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
"index e69de29..9ef167c 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -0,0 +1 @@",
"+(f, g) => { return h; };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "d8b95c6c259bbc1031068e76b71ee165a32fcc90"
"shas": "d700dc51fee7a3dd557906dcdf46d426285d7955..edda3c60ac532d534d84539648fa827ff18a6c59"
}
,{
"testCaseDescription": "javascript-arrow-function-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "d8b95c6c259bbc1031068e76b71ee165a32fcc90",
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
"index 9ef167c..92dea6f 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1 +1,3 @@",
"+(f, g) => { return g; };",
"+(f, g) => { return h; };",
" (f, g) => { return h; };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "38971f3bb12072ce71a8af2e61b40128e2e04335"
"shas": "edda3c60ac532d534d84539648fa827ff18a6c59..63fd87f8cafc4a46f2927f9825cc20e5f116a093"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-insert-test",
@ -114,9 +130,19 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "38971f3bb12072ce71a8af2e61b40128e2e04335",
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
"index 92dea6f..8f5bb51 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1,3 +1,3 @@",
"-(f, g) => { return g; };",
"+(f, g) => { return h; };",
" (f, g) => { return h; };",
" (f, g) => { return h; };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "0bad91b1393996893c42c7ca6cea6b485ed79f3d"
"shas": "63fd87f8cafc4a46f2927f9825cc20e5f116a093..29b18be738dde19aa61343c5f4e54bf83f4b30ea"
}
,{
"testCaseDescription": "javascript-arrow-function-replacement-test",
@ -157,9 +183,19 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "0bad91b1393996893c42c7ca6cea6b485ed79f3d",
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
"index 8f5bb51..92dea6f 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1,3 +1,3 @@",
"-(f, g) => { return h; };",
"+(f, g) => { return g; };",
" (f, g) => { return h; };",
" (f, g) => { return h; };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "22eb88fd92a0f54db863a2c99e7f6cefd573d70c"
"shas": "29b18be738dde19aa61343c5f4e54bf83f4b30ea..d92f900ef9873f273da632ea9c54adcd7acc7961"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-replacement-test",
@ -218,9 +254,19 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "22eb88fd92a0f54db863a2c99e7f6cefd573d70c",
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
"index 92dea6f..acab9a9 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1,3 +1,2 @@",
"-(f, g) => { return g; };",
"-(f, g) => { return h; };",
" (f, g) => { return h; };",
"+(f, g) => { return g; };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "ce32c18979a6f118f1a64d68058aea090fbd6ffa"
"shas": "d92f900ef9873f273da632ea9c54adcd7acc7961..243f2be7291992566bd0ab2c2caef9e7ac13e02d"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-test",
@ -249,9 +295,17 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "ce32c18979a6f118f1a64d68058aea090fbd6ffa",
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
"index acab9a9..ef1be25 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1,2 +1 @@",
"-(f, g) => { return h; };",
" (f, g) => { return g; };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "555a09419c1aeebf5676d25753625cc4a6558f9b"
"shas": "243f2be7291992566bd0ab2c2caef9e7ac13e02d..3128237c6d11459cf7d3e9add902e7be8d38710b"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-rest-test",
@ -280,7 +334,14 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "555a09419c1aeebf5676d25753625cc4a6558f9b",
"patch": [
"diff --git a/arrow-function.js b/arrow-function.js",
"index ef1be25..e69de29 100644",
"--- a/arrow-function.js",
"+++ b/arrow-function.js",
"@@ -1 +0,0 @@",
"-(f, g) => { return g; };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "843b9d83e2acc3f1bf014abc4e2402e1a783d3f6"
"shas": "3128237c6d11459cf7d3e9add902e7be8d38710b..5cab8720cde055f6d78f5c5deaf8980b89a434e1"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"assignment.js"
],
"sha1": "f5dfc0945ffae36e0f9784dcfeb8472344055afc",
"patch": [
"diff --git a/assignment.js b/assignment.js",
"index e69de29..6882fe5 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -0,0 +1 @@",
"+x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "6fc2b9a8bdab5a87aeb8214b88ddafb278098394"
"shas": "10c888c0caabf36cb211a96640afbe435dfad3fb..6a5eb86577a86881fdd53c3db17dd589617b887e"
}
,{
"testCaseDescription": "javascript-assignment-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"assignment.js"
],
"sha1": "6fc2b9a8bdab5a87aeb8214b88ddafb278098394",
"patch": [
"diff --git a/assignment.js b/assignment.js",
"index 6882fe5..fb4cba4 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1 +1,3 @@",
"+x = 1;",
"+x = 0;",
" x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "45ee00517df6dd2f5c12523b82f4ae9c361cbbab"
"shas": "6a5eb86577a86881fdd53c3db17dd589617b887e..79ca8610276bd0cc32d257702e20ec268187f1b6"
}
,{
"testCaseDescription": "javascript-assignment-delete-insert-test",
@ -114,9 +130,19 @@
"filePaths": [
"assignment.js"
],
"sha1": "45ee00517df6dd2f5c12523b82f4ae9c361cbbab",
"patch": [
"diff --git a/assignment.js b/assignment.js",
"index fb4cba4..42e16c6 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1,3 +1,3 @@",
"-x = 1;",
"+x = 0;",
" x = 0;",
" x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "c68a9ee4c0811ebc8bc6a97087ad578bda055575"
"shas": "79ca8610276bd0cc32d257702e20ec268187f1b6..c3da25392def8e82aaf0179cdd8cc51849d805c8"
}
,{
"testCaseDescription": "javascript-assignment-replacement-test",
@ -157,9 +183,19 @@
"filePaths": [
"assignment.js"
],
"sha1": "c68a9ee4c0811ebc8bc6a97087ad578bda055575",
"patch": [
"diff --git a/assignment.js b/assignment.js",
"index 42e16c6..fb4cba4 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1,3 +1,3 @@",
"-x = 0;",
"+x = 1;",
" x = 0;",
" x = 0;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "aa18ede37e29b97d5478771c02f899c26ed29ec8"
"shas": "c3da25392def8e82aaf0179cdd8cc51849d805c8..be4979757f9464e59b4b7fb7dbdce17f4f362029"
}
,{
"testCaseDescription": "javascript-assignment-delete-replacement-test",
@ -218,9 +254,19 @@
"filePaths": [
"assignment.js"
],
"sha1": "aa18ede37e29b97d5478771c02f899c26ed29ec8",
"patch": [
"diff --git a/assignment.js b/assignment.js",
"index fb4cba4..11fe15d 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1,3 +1,2 @@",
"-x = 1;",
"-x = 0;",
" x = 0;",
"+x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "e34fae4bc40de3527a8af142718f5034b8c89464"
"shas": "be4979757f9464e59b4b7fb7dbdce17f4f362029..592d4d9a24fe20282bbaa1cf66bbe20959d47ae5"
}
,{
"testCaseDescription": "javascript-assignment-delete-test",
@ -249,9 +295,17 @@
"filePaths": [
"assignment.js"
],
"sha1": "e34fae4bc40de3527a8af142718f5034b8c89464",
"patch": [
"diff --git a/assignment.js b/assignment.js",
"index 11fe15d..198b8f8 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1,2 +1 @@",
"-x = 0;",
" x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "844f1b80889b328b7de377506a20fd1e07722c3c"
"shas": "592d4d9a24fe20282bbaa1cf66bbe20959d47ae5..f0b77709f5be6c1d671a943d73b8fbb12344762e"
}
,{
"testCaseDescription": "javascript-assignment-delete-rest-test",
@ -280,7 +334,14 @@
"filePaths": [
"assignment.js"
],
"sha1": "844f1b80889b328b7de377506a20fd1e07722c3c",
"patch": [
"diff --git a/assignment.js b/assignment.js",
"index 198b8f8..e69de29 100644",
"--- a/assignment.js",
"+++ b/assignment.js",
"@@ -1 +0,0 @@",
"-x = 1;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "45a5360969a82ef1602c4fd2629a242bd75a1edf"
"shas": "f0b77709f5be6c1d671a943d73b8fbb12344762e..83f3153b76f49e077237997c965dc6f3c3a159bc"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "761fc16b7840013a3a30a594193222af2c710535",
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
"index e69de29..021cf6a 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -0,0 +1 @@",
"+i >> j;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "ae0665071ff8d408f9dba2bc188c7ee5e6d72c8e"
"shas": "5edf134e2ccb0fa1cd27b2e07b4279575f1a5f0d..e2e6f5b9a61fa806befb17711cf3ae52dd20f725"
}
,{
"testCaseDescription": "javascript-bitwise-operator-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "ae0665071ff8d408f9dba2bc188c7ee5e6d72c8e",
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
"index 021cf6a..3e0b6c1 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1 +1,3 @@",
"+i >> k;",
"+i >> j;",
" i >> j;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "30a3708b6b22a2fecb6a2e10ac27b6945a87f9f7"
"shas": "e2e6f5b9a61fa806befb17711cf3ae52dd20f725..de455af0e3ab990d8f20a4555d4bf28324551ed0"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-insert-test",
@ -114,9 +130,19 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "30a3708b6b22a2fecb6a2e10ac27b6945a87f9f7",
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
"index 3e0b6c1..18853d1 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1,3 +1,3 @@",
"-i >> k;",
"+i >> j;",
" i >> j;",
" i >> j;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b5a0645c9262b7ef092240be639ac5cf0758cf64"
"shas": "de455af0e3ab990d8f20a4555d4bf28324551ed0..59f5fd5cc14501c063c3ec3b9563503a4f22537b"
}
,{
"testCaseDescription": "javascript-bitwise-operator-replacement-test",
@ -157,9 +183,19 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "b5a0645c9262b7ef092240be639ac5cf0758cf64",
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
"index 18853d1..3e0b6c1 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1,3 +1,3 @@",
"-i >> j;",
"+i >> k;",
" i >> j;",
" i >> j;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "d2dc484eb040a787945e88294a926f120fed4e12"
"shas": "59f5fd5cc14501c063c3ec3b9563503a4f22537b..24328d0f069d5e61a5926bedf6e0a074361d7477"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-replacement-test",
@ -218,9 +254,19 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "d2dc484eb040a787945e88294a926f120fed4e12",
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
"index 3e0b6c1..ee7d8de 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1,3 +1,2 @@",
"-i >> k;",
"-i >> j;",
" i >> j;",
"+i >> k;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "8411bfe78b348cf56e382a55f6c1bd8541bda049"
"shas": "24328d0f069d5e61a5926bedf6e0a074361d7477..083807f60ce4fd39ee7612cb97e2dc2351a09203"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-test",
@ -249,9 +295,17 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "8411bfe78b348cf56e382a55f6c1bd8541bda049",
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
"index ee7d8de..2800c8c 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1,2 +1 @@",
"-i >> j;",
" i >> k;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "12c46cd84849f5766fff9bdf00c5b8357667c02b"
"shas": "083807f60ce4fd39ee7612cb97e2dc2351a09203..1bceab9d521db6e74ccfca50dae11d9ac030a4bc"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-rest-test",
@ -280,7 +334,14 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "12c46cd84849f5766fff9bdf00c5b8357667c02b",
"patch": [
"diff --git a/bitwise-operator.js b/bitwise-operator.js",
"index 2800c8c..e69de29 100644",
"--- a/bitwise-operator.js",
"+++ b/bitwise-operator.js",
"@@ -1 +0,0 @@",
"-i >> k;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "149d0a9500261cd37b696c4ab2527d34f0133522"
"shas": "1bceab9d521db6e74ccfca50dae11d9ac030a4bc..4e47562dd59646a6c6c55ab138660495394bc5c9"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "0f277a98ca88f6c1e02d2811fa15b32c1909edf0",
"patch": [
"diff --git a/boolean-operator.js b/boolean-operator.js",
"index e69de29..7280a98 100644",
"--- a/boolean-operator.js",
"+++ b/boolean-operator.js",
"@@ -0,0 +1 @@",
"+i || j;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "d039a78308a35a509cecb57ba239162e939925ae"
"shas": "69248e3fdb3e6ab7da864ef7bd3a915aeefd3cc4..697a361cfb8bcfd14631209deb6159679d166115"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "d039a78308a35a509cecb57ba239162e939925ae",
"patch": [
"diff --git a/boolean-operator.js b/boolean-operator.js",
"index 7280a98..fe3f306 100644",
"--- a/boolean-operator.js",
"+++ b/boolean-operator.js",
"@@ -1 +1,3 @@",
"+i && j;",
"+i || j;",
" i || j;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9f2ce7d364ba8f68e4aaf3f2a1bc525afb0fbcfc"
"shas": "697a361cfb8bcfd14631209deb6159679d166115..2829490ad0cdc2f954145a2698444d5daf1da199"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-insert-test",
@ -84,9 +100,19 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "9f2ce7d364ba8f68e4aaf3f2a1bc525afb0fbcfc",
"patch": [
"diff --git a/boolean-operator.js b/boolean-operator.js",
"index fe3f306..273c0ee 100644",
"--- a/boolean-operator.js",
"+++ b/boolean-operator.js",
"@@ -1,3 +1,3 @@",
"-i && j;",
"+i || j;",
" i || j;",
" i || j;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9f9d0f34d19c5335218140e896e56cca5483085c"
"shas": "2829490ad0cdc2f954145a2698444d5daf1da199..8a66944201f7ad0fc2ee8fcdcaff607125c8cc0f"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-test",
@ -97,9 +123,19 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "9f9d0f34d19c5335218140e896e56cca5483085c",
"patch": [
"diff --git a/boolean-operator.js b/boolean-operator.js",
"index 273c0ee..fe3f306 100644",
"--- a/boolean-operator.js",
"+++ b/boolean-operator.js",
"@@ -1,3 +1,3 @@",
"-i || j;",
"+i && j;",
" i || j;",
" i || j;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b7735561df1e286eb16fbd6d6f12c40f33f0d884"
"shas": "8a66944201f7ad0fc2ee8fcdcaff607125c8cc0f..0658cb117a6a6719f8464948c86e3e278d8c2a95"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-replacement-test",
@ -128,9 +164,19 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "b7735561df1e286eb16fbd6d6f12c40f33f0d884",
"patch": [
"diff --git a/boolean-operator.js b/boolean-operator.js",
"index fe3f306..7f4873c 100644",
"--- a/boolean-operator.js",
"+++ b/boolean-operator.js",
"@@ -1,3 +1,2 @@",
"-i && j;",
"-i || j;",
" i || j;",
"+i && j;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "4209ac85ff7d9fdbe9ac2d309fefec0af45d0702"
"shas": "0658cb117a6a6719f8464948c86e3e278d8c2a95..35f6d8f480c9f8645a3c0d8f9fa5339059a6380a"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-test",
@ -159,9 +205,17 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "4209ac85ff7d9fdbe9ac2d309fefec0af45d0702",
"patch": [
"diff --git a/boolean-operator.js b/boolean-operator.js",
"index 7f4873c..c6921d1 100644",
"--- a/boolean-operator.js",
"+++ b/boolean-operator.js",
"@@ -1,2 +1 @@",
"-i || j;",
" i && j;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "2ee56bee510724715c14244f51c38c55b13ed274"
"shas": "35f6d8f480c9f8645a3c0d8f9fa5339059a6380a..2b07585de8be3e4334361368f2dc465278842434"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-rest-test",
@ -190,7 +244,14 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "2ee56bee510724715c14244f51c38c55b13ed274",
"patch": [
"diff --git a/boolean-operator.js b/boolean-operator.js",
"index c6921d1..e69de29 100644",
"--- a/boolean-operator.js",
"+++ b/boolean-operator.js",
"@@ -1 +0,0 @@",
"-i && j;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "761fc16b7840013a3a30a594193222af2c710535"
"shas": "2b07585de8be3e4334361368f2dc465278842434..5edf134e2ccb0fa1cd27b2e07b4279575f1a5f0d"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "0dd5a42b7e992a63ee0e46bbbc58699dd09f6851",
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
"index e69de29..ce9ee1e 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -0,0 +1 @@",
"+this.map(function (a) { return a.b; })"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "5a141e4ade0038fbde994ab77049a38a1565b976"
"shas": "1512ae1cef2a096ce2723ce98334e4ce0e4bc82b..2a014ee8fd6ea4f8ce5b6bae0ca35a4fa6462deb"
}
,{
"testCaseDescription": "javascript-chained-callbacks-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "5a141e4ade0038fbde994ab77049a38a1565b976",
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
"index ce9ee1e..acba744 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1 +1,3 @@",
"+this.reduce(function (a) { return b.a; })",
"+this.map(function (a) { return a.b; })",
" this.map(function (a) { return a.b; })"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "8bb88ee35fe50732fa664a022dab4f67d4fad2a3"
"shas": "2a014ee8fd6ea4f8ce5b6bae0ca35a4fa6462deb..6a6e1ae99abc9cae5f8ac31aac43836380944603"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-insert-test",
@ -168,9 +184,19 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "8bb88ee35fe50732fa664a022dab4f67d4fad2a3",
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
"index acba744..7390534 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1,3 +1,3 @@",
"-this.reduce(function (a) { return b.a; })",
"+this.map(function (a) { return a.b; })",
" this.map(function (a) { return a.b; })",
" this.map(function (a) { return a.b; })"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "20f50a2164ac72df558b6ba29253a750d0e43b30"
"shas": "6a6e1ae99abc9cae5f8ac31aac43836380944603..c86429cb689c74e2ce3988c8bc257a365734cbe3"
}
,{
"testCaseDescription": "javascript-chained-callbacks-replacement-test",
@ -265,9 +291,19 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "20f50a2164ac72df558b6ba29253a750d0e43b30",
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
"index 7390534..acba744 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1,3 +1,3 @@",
"-this.map(function (a) { return a.b; })",
"+this.reduce(function (a) { return b.a; })",
" this.map(function (a) { return a.b; })",
" this.map(function (a) { return a.b; })"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "0df44200409e2bc7040f464d19c0105073aa8e0a"
"shas": "c86429cb689c74e2ce3988c8bc257a365734cbe3..c4df0b8afdd73cae6d89a9098ae38d9c3085dbb8"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-replacement-test",
@ -326,9 +362,19 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "0df44200409e2bc7040f464d19c0105073aa8e0a",
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
"index acba744..c4db432 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1,3 +1,2 @@",
"-this.reduce(function (a) { return b.a; })",
"-this.map(function (a) { return a.b; })",
" this.map(function (a) { return a.b; })",
"+this.reduce(function (a) { return b.a; })"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "7e75f5dee9344c80bf09a677752c16c9ca0ee945"
"shas": "c4df0b8afdd73cae6d89a9098ae38d9c3085dbb8..8b7dbbb0ca20e47dfed24fb3eb3a790721d2e9d0"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-test",
@ -357,9 +403,17 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "7e75f5dee9344c80bf09a677752c16c9ca0ee945",
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
"index c4db432..e593419 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1,2 +1 @@",
"-this.map(function (a) { return a.b; })",
" this.reduce(function (a) { return b.a; })"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "0313d7b16c660931a9fcba9a02f3f79dcb16ad95"
"shas": "8b7dbbb0ca20e47dfed24fb3eb3a790721d2e9d0..e2c2e86db834a0ab3c6006c6385e90d780851357"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-rest-test",
@ -388,7 +442,14 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "0313d7b16c660931a9fcba9a02f3f79dcb16ad95",
"patch": [
"diff --git a/chained-callbacks.js b/chained-callbacks.js",
"index e593419..e69de29 100644",
"--- a/chained-callbacks.js",
"+++ b/chained-callbacks.js",
"@@ -1 +0,0 @@",
"-this.reduce(function (a) { return b.a; })"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "1a9472e94c365639f5f2b5c519a06c2daf17c630"
"shas": "e2c2e86db834a0ab3c6006c6385e90d780851357..5ef42771e35b5af39f3befe137fedf40f174a5c7"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "d634acd5aed3ab7ef4a9914234758a3bf356d2c4",
"patch": [
"diff --git a/chained-property-access.js b/chained-property-access.js",
"index e69de29..5914a55 100644",
"--- a/chained-property-access.js",
"+++ b/chained-property-access.js",
"@@ -0,0 +1 @@",
"+return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "723940f8df7814d9f0fb1ea03dddbff771d80ac8"
"shas": "71feda9fd80ab60adab5cf81748710b2a610173f..02c42e637780aeb5874c5f740ba764a0b606d950"
}
,{
"testCaseDescription": "javascript-chained-property-access-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "723940f8df7814d9f0fb1ea03dddbff771d80ac8",
"patch": [
"diff --git a/chained-property-access.js b/chained-property-access.js",
"index 5914a55..7095976 100644",
"--- a/chained-property-access.js",
"+++ b/chained-property-access.js",
"@@ -1 +1,3 @@",
"+return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
"+return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "4d9c7053f056b963074f086d40020195bff90c32"
"shas": "02c42e637780aeb5874c5f740ba764a0b606d950..eb64ebf3bc9351da0d4cbb59cdfc44d7152b090e"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-insert-test",
@ -141,9 +157,19 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "4d9c7053f056b963074f086d40020195bff90c32",
"patch": [
"diff --git a/chained-property-access.js b/chained-property-access.js",
"index 7095976..98df938 100644",
"--- a/chained-property-access.js",
"+++ b/chained-property-access.js",
"@@ -1,3 +1,3 @@",
"-return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
"+return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b0faefc21e5b571d399056063f96cfbf810a503f"
"shas": "eb64ebf3bc9351da0d4cbb59cdfc44d7152b090e..d87ef7df3e23f3b4837c9dd09aeca869774aa731"
}
,{
"testCaseDescription": "javascript-chained-property-access-replacement-test",
@ -211,9 +237,19 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "b0faefc21e5b571d399056063f96cfbf810a503f",
"patch": [
"diff --git a/chained-property-access.js b/chained-property-access.js",
"index 98df938..7095976 100644",
"--- a/chained-property-access.js",
"+++ b/chained-property-access.js",
"@@ -1,3 +1,3 @@",
"-return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
"+return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "ea742ea1e997a7a1241d1e719c3b313d8a42067c"
"shas": "d87ef7df3e23f3b4837c9dd09aeca869774aa731..2e00036e857c5aa6af0eb4ab23bd4cbb28bd90a2"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-replacement-test",
@ -272,9 +308,19 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "ea742ea1e997a7a1241d1e719c3b313d8a42067c",
"patch": [
"diff --git a/chained-property-access.js b/chained-property-access.js",
"index 7095976..7b764ca 100644",
"--- a/chained-property-access.js",
"+++ b/chained-property-access.js",
"@@ -1,3 +1,2 @@",
"-return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )",
"-return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
" return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
"+return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "5517a9b89409234d2dc3cbf17aa526d72bc12479"
"shas": "2e00036e857c5aa6af0eb4ab23bd4cbb28bd90a2..5eb335f13f0dea85c75b4d5f174832b08af8a0e6"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-test",
@ -303,9 +349,17 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "5517a9b89409234d2dc3cbf17aa526d72bc12479",
"patch": [
"diff --git a/chained-property-access.js b/chained-property-access.js",
"index 7b764ca..5d6d3a0 100644",
"--- a/chained-property-access.js",
"+++ b/chained-property-access.js",
"@@ -1,2 +1 @@",
"-return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )",
" return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "66cacfd430f02a62b6976e31fdc0a53ae019dd5e"
"shas": "5eb335f13f0dea85c75b4d5f174832b08af8a0e6..054acb661f91e8a5b9096d552c5b3410bacc4811"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-rest-test",
@ -334,7 +388,14 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "66cacfd430f02a62b6976e31fdc0a53ae019dd5e",
"patch": [
"diff --git a/chained-property-access.js b/chained-property-access.js",
"index 5d6d3a0..e69de29 100644",
"--- a/chained-property-access.js",
"+++ b/chained-property-access.js",
"@@ -1 +0,0 @@",
"-return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "0dd5a42b7e992a63ee0e46bbbc58699dd09f6851"
"shas": "054acb661f91e8a5b9096d552c5b3410bacc4811..1512ae1cef2a096ce2723ce98334e4ce0e4bc82b"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"class.js"
],
"sha1": "559546b09a86fffc79e8283d8f7567d491c07e90",
"patch": [
"diff --git a/class.js b/class.js",
"index e69de29..8f6ae64 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -0,0 +1 @@",
"+class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "0ac57022cf74cb78426a1df060ce3ac2ff83cd71"
"shas": "f6dfeb42af9db740677fd60341ea39da711f7c81..f071d25d12bb0086a285449efbe5cfaeeed8e436"
}
,{
"testCaseDescription": "javascript-class-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"class.js"
],
"sha1": "0ac57022cf74cb78426a1df060ce3ac2ff83cd71",
"patch": [
"diff --git a/class.js b/class.js",
"index 8f6ae64..b509437 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -1 +1,3 @@",
"+class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
"+class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
" class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "5bbc894719630d0236a85728f425e98a4ef3487b"
"shas": "f071d25d12bb0086a285449efbe5cfaeeed8e436..ba736a07888eb4991323c035f2bf78fe1650ea56"
}
,{
"testCaseDescription": "javascript-class-delete-insert-test",
@ -105,7 +121,7 @@
}
]
},
"summary": "Replaced the 'foo' identifier with the 'one' identifier in the one method of the 'Foo' class"
"summary": "Replaced the 'foo' identifier with the 'one' identifier in the 'one(a)' method of the 'Foo' class"
},
{
"span": {
@ -120,7 +136,7 @@
]
}
},
"summary": "Added the 'two' method in the Foo class"
"summary": "Added the 'two(b)' method in the Foo class"
},
{
"span": {
@ -135,7 +151,7 @@
]
}
},
"summary": "Added the 'three' method in the Foo class"
"summary": "Added the 'three(c)' method in the Foo class"
},
{
"span": {
@ -150,7 +166,7 @@
]
}
},
"summary": "Deleted the 'bar' method in the Foo class"
"summary": "Deleted the 'bar(b)' method in the Foo class"
},
{
"span": {
@ -165,7 +181,7 @@
]
}
},
"summary": "Deleted the 'baz' method in the Foo class"
"summary": "Deleted the 'baz(c)' method in the Foo class"
}
]
},
@ -174,9 +190,19 @@
"filePaths": [
"class.js"
],
"sha1": "5bbc894719630d0236a85728f425e98a4ef3487b",
"patch": [
"diff --git a/class.js b/class.js",
"index b509437..c4f5c91 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -1,3 +1,3 @@",
"-class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
"+class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
" class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
" class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "7e7e2be0141ca3710f3a774caa03f4704e9d3586"
"shas": "ba736a07888eb4991323c035f2bf78fe1650ea56..c99d7b8dc9cff808ef1e6010caa4573ad1694d9b"
}
,{
"testCaseDescription": "javascript-class-replacement-test",
@ -208,7 +234,7 @@
}
]
},
"summary": "Replaced the 'one' identifier with the 'foo' identifier in the foo method of the 'Foo' class"
"summary": "Replaced the 'one' identifier with the 'foo' identifier in the 'foo(a)' method of the 'Foo' class"
},
{
"span": {
@ -223,7 +249,7 @@
]
}
},
"summary": "Added the 'bar' method in the Foo class"
"summary": "Added the 'bar(b)' method in the Foo class"
},
{
"span": {
@ -238,7 +264,7 @@
]
}
},
"summary": "Added the 'baz' method in the Foo class"
"summary": "Added the 'baz(c)' method in the Foo class"
},
{
"span": {
@ -253,7 +279,7 @@
]
}
},
"summary": "Deleted the 'two' method in the Foo class"
"summary": "Deleted the 'two(b)' method in the Foo class"
},
{
"span": {
@ -268,7 +294,7 @@
]
}
},
"summary": "Deleted the 'three' method in the Foo class"
"summary": "Deleted the 'three(c)' method in the Foo class"
}
]
},
@ -277,9 +303,19 @@
"filePaths": [
"class.js"
],
"sha1": "7e7e2be0141ca3710f3a774caa03f4704e9d3586",
"patch": [
"diff --git a/class.js b/class.js",
"index c4f5c91..b509437 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -1,3 +1,3 @@",
"-class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
"+class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
" class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
" class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "f67a4f59fd14475400023beebe947c59aea5f3ea"
"shas": "c99d7b8dc9cff808ef1e6010caa4573ad1694d9b..75a0caa880f62a0706ff723f555a9ec1f0c53c29"
}
,{
"testCaseDescription": "javascript-class-delete-replacement-test",
@ -338,9 +374,19 @@
"filePaths": [
"class.js"
],
"sha1": "f67a4f59fd14475400023beebe947c59aea5f3ea",
"patch": [
"diff --git a/class.js b/class.js",
"index b509437..b1ef404 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -1,3 +1,2 @@",
"-class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }",
"-class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
" class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
"+class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "ef1f76b5f01fce4b330b99a4ebf3b128c03b7cb1"
"shas": "75a0caa880f62a0706ff723f555a9ec1f0c53c29..4231a3b306d145aa37ceb879ef6f8da6221e54b8"
}
,{
"testCaseDescription": "javascript-class-delete-test",
@ -369,9 +415,17 @@
"filePaths": [
"class.js"
],
"sha1": "ef1f76b5f01fce4b330b99a4ebf3b128c03b7cb1",
"patch": [
"diff --git a/class.js b/class.js",
"index b1ef404..2c17f72 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -1,2 +1 @@",
"-class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }",
" class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "db58ab719fe45f004df748e0e6248d756f7ad9f3"
"shas": "4231a3b306d145aa37ceb879ef6f8da6221e54b8..d5627235989da4028cfcb15c4b1ee2bdc544fd31"
}
,{
"testCaseDescription": "javascript-class-delete-rest-test",
@ -400,7 +454,14 @@
"filePaths": [
"class.js"
],
"sha1": "db58ab719fe45f004df748e0e6248d756f7ad9f3",
"patch": [
"diff --git a/class.js b/class.js",
"index 2c17f72..e69de29 100644",
"--- a/class.js",
"+++ b/class.js",
"@@ -1 +0,0 @@",
"-class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9ccab273233837d842e68ec909416aab24ff359a"
"shas": "d5627235989da4028cfcb15c4b1ee2bdc544fd31..654a538b26c9b4c8637e6c2e4cd497c93e690310"
}]

View File

@ -40,9 +40,16 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "653a2a2b908c1963d4682a6e4b6e89f1aa17b275",
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
"index e69de29..cff019f 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -0,0 +1 @@",
"+a = 1, b = 2;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "7d8c6c9fdcb9ab7e9f40ae14efc813ae2b67e19e"
"shas": "ec86aaba01801d01aca70fd31403642be1e2d438..b0a5f928a8a4594bb176a56275c43ccab6e2e2a0"
}
,{
"testCaseDescription": "javascript-comma-operator-replacement-insert-test",
@ -101,9 +108,18 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "7d8c6c9fdcb9ab7e9f40ae14efc813ae2b67e19e",
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
"index cff019f..93ece10 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1 +1,3 @@",
"+c = {d: (3, 4 + 5, 6)};",
"+a = 1, b = 2;",
" a = 1, b = 2;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "40847aa7f589fd835e91320d43628d16fd37ef15"
"shas": "b0a5f928a8a4594bb176a56275c43ccab6e2e2a0..315b46ccdb9a45c374b4ed1cc51a062d74c13a78"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-insert-test",
@ -162,9 +178,19 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "40847aa7f589fd835e91320d43628d16fd37ef15",
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
"index 93ece10..f738c2d 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1,3 +1,3 @@",
"-c = {d: (3, 4 + 5, 6)};",
"+a = 1, b = 2;",
" a = 1, b = 2;",
" a = 1, b = 2;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b244fddf952c3cadad8f104cc2ee2abbf93dafcf"
"shas": "315b46ccdb9a45c374b4ed1cc51a062d74c13a78..30cf69eb0cc5543fe53be82f29cd0e0371e30cd1"
}
,{
"testCaseDescription": "javascript-comma-operator-replacement-test",
@ -223,9 +249,19 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "b244fddf952c3cadad8f104cc2ee2abbf93dafcf",
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
"index f738c2d..93ece10 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1,3 +1,3 @@",
"-a = 1, b = 2;",
"+c = {d: (3, 4 + 5, 6)};",
" a = 1, b = 2;",
" a = 1, b = 2;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "f40060278cf7bbaca75632570dbadc10067591bb"
"shas": "30cf69eb0cc5543fe53be82f29cd0e0371e30cd1..a454c132f64a253a51cbf1a1455e74fca9343c23"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-replacement-test",
@ -299,9 +335,19 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "f40060278cf7bbaca75632570dbadc10067591bb",
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
"index 93ece10..297e28d 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1,3 +1,2 @@",
"-c = {d: (3, 4 + 5, 6)};",
"-a = 1, b = 2;",
" a = 1, b = 2;",
"+c = {d: (3, 4 + 5, 6)};"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "67e74b7145a061c1d8f576792167aab68c6be809"
"shas": "a454c132f64a253a51cbf1a1455e74fca9343c23..db24ea61ad00e73c91b0a4b616f333a5eac48f29"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-test",
@ -345,9 +391,17 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "67e74b7145a061c1d8f576792167aab68c6be809",
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
"index 297e28d..421bc7f 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1,2 +1 @@",
"-a = 1, b = 2;",
" c = {d: (3, 4 + 5, 6)};"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "12ce4e2077d01b8c8209ad272f1d0f715d9b0124"
"shas": "db24ea61ad00e73c91b0a4b616f333a5eac48f29..4ec8128c2ab11f7bf00c002d0fec6c8601b14c16"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-rest-test",
@ -376,7 +430,14 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "12ce4e2077d01b8c8209ad272f1d0f715d9b0124",
"patch": [
"diff --git a/comma-operator.js b/comma-operator.js",
"index 421bc7f..e69de29 100644",
"--- a/comma-operator.js",
"+++ b/comma-operator.js",
"@@ -1 +0,0 @@",
"-c = {d: (3, 4 + 5, 6)};"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "26df3b54cd036f1ed2bff8a0ca225ad680e23432"
"shas": "4ec8128c2ab11f7bf00c002d0fec6c8601b14c16..0ccf8092231ebc8ac92cc60fe614f1681bc03a89"
}]

View File

@ -7,9 +7,16 @@
"filePaths": [
"comment.js"
],
"sha1": "51cb9277c2233716e2f002c08a23656f70425838",
"patch": [
"diff --git a/comment.js b/comment.js",
"index e69de29..a5821d2 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -0,0 +1 @@",
"+// This is a property"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "98ef3ccd95e55e93513f790185e4fc83ed93def2"
"shas": "81bc4513ad3979452e9e95586a5fbc9ca66eeadc..522a93132b55605393a0f7a5421f3d1f7b0d4a8c"
}
,{
"testCaseDescription": "javascript-comment-replacement-insert-test",
@ -20,9 +27,20 @@
"filePaths": [
"comment.js"
],
"sha1": "98ef3ccd95e55e93513f790185e4fc83ed93def2",
"patch": [
"diff --git a/comment.js b/comment.js",
"index a5821d2..761aa7a 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1 +1,5 @@",
"+/*",
"+ * This is a method",
"+*/",
"+// This is a property",
" // This is a property"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "1ac3dd727429b94a67241d8941f5360892a30fae"
"shas": "522a93132b55605393a0f7a5421f3d1f7b0d4a8c..f0aa09e8712b14d61160b16073cac5fbd0276038"
}
,{
"testCaseDescription": "javascript-comment-delete-insert-test",
@ -33,9 +51,21 @@
"filePaths": [
"comment.js"
],
"sha1": "1ac3dd727429b94a67241d8941f5360892a30fae",
"patch": [
"diff --git a/comment.js b/comment.js",
"index 761aa7a..3b33406 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1,5 +1,3 @@",
"-/*",
"- * This is a method",
"-*/",
"+// This is a property",
" // This is a property",
" // This is a property"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "722ca07f3cc31c8d961494547fab727ec588e3d8"
"shas": "f0aa09e8712b14d61160b16073cac5fbd0276038..9402b254de81dabcddcbd6d7308911822b6f0f59"
}
,{
"testCaseDescription": "javascript-comment-replacement-test",
@ -46,9 +76,21 @@
"filePaths": [
"comment.js"
],
"sha1": "722ca07f3cc31c8d961494547fab727ec588e3d8",
"patch": [
"diff --git a/comment.js b/comment.js",
"index 3b33406..761aa7a 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1,3 +1,5 @@",
"-// This is a property",
"+/*",
"+ * This is a method",
"+*/",
" // This is a property",
" // This is a property"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "ddbe0bb45770aad94db0b3db41bb85c6cf8667ea"
"shas": "9402b254de81dabcddcbd6d7308911822b6f0f59..ba788116c40403584cd03df9976350810a9b1162"
}
,{
"testCaseDescription": "javascript-comment-delete-replacement-test",
@ -59,9 +101,21 @@
"filePaths": [
"comment.js"
],
"sha1": "ddbe0bb45770aad94db0b3db41bb85c6cf8667ea",
"patch": [
"diff --git a/comment.js b/comment.js",
"index 761aa7a..c2a8148 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1,5 +1,4 @@",
"+// This is a property",
" /*",
" * This is a method",
" */",
"-// This is a property",
"-// This is a property"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "16f46467d4d4394f04d1098d53f86503eb75c645"
"shas": "ba788116c40403584cd03df9976350810a9b1162..05a2041be1630b8a7309163d4b863cd8966adbe0"
}
,{
"testCaseDescription": "javascript-comment-delete-test",
@ -72,9 +126,19 @@
"filePaths": [
"comment.js"
],
"sha1": "16f46467d4d4394f04d1098d53f86503eb75c645",
"patch": [
"diff --git a/comment.js b/comment.js",
"index c2a8148..7c74dcd 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1,4 +1,3 @@",
"-// This is a property",
" /*",
" * This is a method",
" */"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9be6ce33b023b9caecb8a2b0d01d7b040aa4da21"
"shas": "05a2041be1630b8a7309163d4b863cd8966adbe0..28ae9fb48ab99b60a709d3168a82f53017fa27a0"
}
,{
"testCaseDescription": "javascript-comment-delete-rest-test",
@ -85,7 +149,16 @@
"filePaths": [
"comment.js"
],
"sha1": "9be6ce33b023b9caecb8a2b0d01d7b040aa4da21",
"patch": [
"diff --git a/comment.js b/comment.js",
"index 7c74dcd..e69de29 100644",
"--- a/comment.js",
"+++ b/comment.js",
"@@ -1,3 +0,0 @@",
"-/*",
"- * This is a method",
"-*/"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "3061e328305d93ca2fd3a8aa7a86d645c4c28b15"
"shas": "28ae9fb48ab99b60a709d3168a82f53017fa27a0..8f7edd21ecef61769b82fb5a60a881f31ce30a01"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "3bd8ebcbe86dd538120a517b6420d768e8ce2b4c",
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
"index e69de29..9d723b9 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -0,0 +1 @@",
"+new module.Klass(1, \"two\");"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "ce70ddd02a33da6279c6bf17d449df82c8832841"
"shas": "b1ed87edc6bf561edc524058ab781a95970a3258..692f777ed1db0b3284bd2728f6c651425e20ab34"
}
,{
"testCaseDescription": "javascript-constructor-call-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "ce70ddd02a33da6279c6bf17d449df82c8832841",
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
"index 9d723b9..2c91b11 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1 +1,3 @@",
"+new module.Klass(1, \"three\");",
"+new module.Klass(1, \"two\");",
" new module.Klass(1, \"two\");"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "8487448225b5505389343c8393596e17ce1a54e8"
"shas": "692f777ed1db0b3284bd2728f6c651425e20ab34..e4d96364ed5caab5be836020193ea527a6cd6e55"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-insert-test",
@ -114,9 +130,19 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "8487448225b5505389343c8393596e17ce1a54e8",
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
"index 2c91b11..892f542 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1,3 +1,3 @@",
"-new module.Klass(1, \"three\");",
"+new module.Klass(1, \"two\");",
" new module.Klass(1, \"two\");",
" new module.Klass(1, \"two\");"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "0eba0fb788d00016c7515ce5c38c413191448474"
"shas": "e4d96364ed5caab5be836020193ea527a6cd6e55..c5f5c7389717f787423d9698a3e0593a965ffbd5"
}
,{
"testCaseDescription": "javascript-constructor-call-replacement-test",
@ -157,9 +183,19 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "0eba0fb788d00016c7515ce5c38c413191448474",
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
"index 892f542..2c91b11 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1,3 +1,3 @@",
"-new module.Klass(1, \"two\");",
"+new module.Klass(1, \"three\");",
" new module.Klass(1, \"two\");",
" new module.Klass(1, \"two\");"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "c1e0930ce2d9e9d05f967ee7857e1a8b7e80b9a2"
"shas": "c5f5c7389717f787423d9698a3e0593a965ffbd5..d17799b023d4e85c6e1d97220121da96a1323970"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-replacement-test",
@ -218,9 +254,19 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "c1e0930ce2d9e9d05f967ee7857e1a8b7e80b9a2",
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
"index 2c91b11..cd77b98 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1,3 +1,2 @@",
"-new module.Klass(1, \"three\");",
"-new module.Klass(1, \"two\");",
" new module.Klass(1, \"two\");",
"+new module.Klass(1, \"three\");"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "723818ee1046fdbb4aed30a93ec6cc212062fdcd"
"shas": "d17799b023d4e85c6e1d97220121da96a1323970..ddc3d491ed287b5aee714bedf5c2de5ba46770ce"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-test",
@ -249,9 +295,17 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "723818ee1046fdbb4aed30a93ec6cc212062fdcd",
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
"index cd77b98..75f6a29 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1,2 +1 @@",
"-new module.Klass(1, \"two\");",
" new module.Klass(1, \"three\");"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "5899cfa5983c7be3dc0c389ca1d0288fb608e98b"
"shas": "ddc3d491ed287b5aee714bedf5c2de5ba46770ce..e0a37e9237220e1382c4502fdfbbb4cc10cf04e0"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-rest-test",
@ -280,7 +334,14 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "5899cfa5983c7be3dc0c389ca1d0288fb608e98b",
"patch": [
"diff --git a/constructor-call.js b/constructor-call.js",
"index 75f6a29..e69de29 100644",
"--- a/constructor-call.js",
"+++ b/constructor-call.js",
"@@ -1 +0,0 @@",
"-new module.Klass(1, \"three\");"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "012105d0edaef241c26098d6e1680dab22bacbbc"
"shas": "e0a37e9237220e1382c4502fdfbbb4cc10cf04e0..41ab7cb7dc378bf229f7a08f1a03c0676483f435"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "979a03e21696fd6d2f5ef3c8c8e7473810cfc7c9",
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
"index e69de29..c83346d 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -0,0 +1 @@",
"+delete thing['prop'];"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b2de3290891a273baacbb28e1b384ac0f6e791ac"
"shas": "b5645de0a9c0002d8f44d302c200dd88ff113f52..d1aaae4cff971b6bd6647c77427eab5789728dea"
}
,{
"testCaseDescription": "javascript-delete-operator-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "b2de3290891a273baacbb28e1b384ac0f6e791ac",
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
"index c83346d..7c8b990 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1 +1,3 @@",
"+delete thing.prop",
"+delete thing['prop'];",
" delete thing['prop'];"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "c15e1d0affd79055bf356a9576a0ccda17249a6f"
"shas": "d1aaae4cff971b6bd6647c77427eab5789728dea..6444b777c04540c4e0229617aaadcf274dbe092f"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-insert-test",
@ -114,9 +130,19 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "c15e1d0affd79055bf356a9576a0ccda17249a6f",
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
"index 7c8b990..f506e36 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1,3 +1,3 @@",
"-delete thing.prop",
"+delete thing['prop'];",
" delete thing['prop'];",
" delete thing['prop'];"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "947df4dfc78c0a7a15d61a245059d9cc66e52823"
"shas": "6444b777c04540c4e0229617aaadcf274dbe092f..ce69f237ff3cf767d8814435ffa957dadfeafa37"
}
,{
"testCaseDescription": "javascript-delete-operator-replacement-test",
@ -157,9 +183,19 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "947df4dfc78c0a7a15d61a245059d9cc66e52823",
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
"index f506e36..7c8b990 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1,3 +1,3 @@",
"-delete thing['prop'];",
"+delete thing.prop",
" delete thing['prop'];",
" delete thing['prop'];"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "f1f49151fc821413654af49d74417c7b200bbb46"
"shas": "ce69f237ff3cf767d8814435ffa957dadfeafa37..71f7d6db03225cbfcc31f2bbd6ab589e9183c55c"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-replacement-test",
@ -218,9 +254,19 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "f1f49151fc821413654af49d74417c7b200bbb46",
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
"index 7c8b990..2dfe079 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1,3 +1,2 @@",
"-delete thing.prop",
"-delete thing['prop'];",
" delete thing['prop'];",
"+delete thing.prop"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9f515bdf829eb8bc34256b20f43923933e001f30"
"shas": "71f7d6db03225cbfcc31f2bbd6ab589e9183c55c..629c83e185f6ed3c97976cc604dfb3c5f455c11b"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-test",
@ -249,9 +295,17 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "9f515bdf829eb8bc34256b20f43923933e001f30",
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
"index 2dfe079..9d68dfb 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1,2 +1 @@",
"-delete thing['prop'];",
" delete thing.prop"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9c59c645ed8417f8fd39ce4094a07c7fcdc009c3"
"shas": "629c83e185f6ed3c97976cc604dfb3c5f455c11b..cf1e4c5bef7af55d4866d7be93a24a523edbbf4f"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-rest-test",
@ -280,7 +334,14 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "9c59c645ed8417f8fd39ce4094a07c7fcdc009c3",
"patch": [
"diff --git a/delete-operator.js b/delete-operator.js",
"index 9d68dfb..e69de29 100644",
"--- a/delete-operator.js",
"+++ b/delete-operator.js",
"@@ -1 +0,0 @@",
"-delete thing.prop"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "003fa853280eb9156b63626be54039b1bc67ea49"
"shas": "cf1e4c5bef7af55d4866d7be93a24a523edbbf4f..56f88d5286e94da2b11b7f6d0a35aa836d4f5921"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "ec8ba8297edb4d6d8dbc00d6f028116e0b58abe8",
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
"index e69de29..d1ec804 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -0,0 +1 @@",
"+do { console.log(insert); } while (true);"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "33549ab5882710be4c88bcfdf659400ce67f5c1d"
"shas": "cd322134775da8db98f5a151ec8e2f5d9eddd3cf..2b58702fac7ff187b0f41a31b6fae16718c0ec4c"
}
,{
"testCaseDescription": "javascript-do-while-statement-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "33549ab5882710be4c88bcfdf659400ce67f5c1d",
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
"index d1ec804..d9a410d 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -1 +1,3 @@",
"+do { console.log(replacement); } while (false);",
"+do { console.log(insert); } while (true);",
" do { console.log(insert); } while (true);"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "969fbb30a28a983aaea07a0caf168258283b9e01"
"shas": "2b58702fac7ff187b0f41a31b6fae16718c0ec4c..fa2041b0ae98229dc1322fda8ebaa2d98dd4b1f7"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-insert-test",
@ -141,9 +157,19 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "969fbb30a28a983aaea07a0caf168258283b9e01",
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
"index d9a410d..4197835 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -1,3 +1,3 @@",
"-do { console.log(replacement); } while (false);",
"+do { console.log(insert); } while (true);",
" do { console.log(insert); } while (true);",
" do { console.log(insert); } while (true);"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b568ea7e0a262c3819571cb8b2b2286eb182583c"
"shas": "fa2041b0ae98229dc1322fda8ebaa2d98dd4b1f7..c7d0a76295cd609ed29a5c857ff2d885eefb3610"
}
,{
"testCaseDescription": "javascript-do-while-statement-replacement-test",
@ -211,9 +237,19 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "b568ea7e0a262c3819571cb8b2b2286eb182583c",
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
"index 4197835..d9a410d 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -1,3 +1,3 @@",
"-do { console.log(insert); } while (true);",
"+do { console.log(replacement); } while (false);",
" do { console.log(insert); } while (true);",
" do { console.log(insert); } while (true);"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "4ae8d06981390b10da59e0f4c795f7d62606283e"
"shas": "c7d0a76295cd609ed29a5c857ff2d885eefb3610..8887ecec6e5dc8852e1f29ffe74c0b79c304e04e"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-replacement-test",
@ -272,9 +308,19 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "4ae8d06981390b10da59e0f4c795f7d62606283e",
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
"index d9a410d..c5291b4 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -1,3 +1,2 @@",
"-do { console.log(replacement); } while (false);",
"-do { console.log(insert); } while (true);",
" do { console.log(insert); } while (true);",
"+do { console.log(replacement); } while (false);"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "f79ad68ff3a0efaed28e9aa75314d2f4705de647"
"shas": "8887ecec6e5dc8852e1f29ffe74c0b79c304e04e..888367feff9a28c449258cd99afd8ac90e069f76"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-test",
@ -303,9 +349,17 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "f79ad68ff3a0efaed28e9aa75314d2f4705de647",
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
"index c5291b4..6085cb1 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -1,2 +1 @@",
"-do { console.log(insert); } while (true);",
" do { console.log(replacement); } while (false);"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "7472b66a363abaae79b52faab6dff2465746424d"
"shas": "888367feff9a28c449258cd99afd8ac90e069f76..622706434ac7e362f28c08d79f7d8302ec086757"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-rest-test",
@ -334,7 +388,14 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "7472b66a363abaae79b52faab6dff2465746424d",
"patch": [
"diff --git a/do-while-statement.js b/do-while-statement.js",
"index 6085cb1..e69de29 100644",
"--- a/do-while-statement.js",
"+++ b/do-while-statement.js",
"@@ -1 +0,0 @@",
"-do { console.log(replacement); } while (false);"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "1c17753ae9931d9d5b151bab4498c78c5b31c6c1"
"shas": "622706434ac7e362f28c08d79f7d8302ec086757..2795ba48a13af4b2c6f240761fd880dc6cd10c2b"
}]

View File

@ -175,9 +175,26 @@
"filePaths": [
"export.js"
],
"sha1": "7b67ddbc527cc15d1cbac33725dc0c4d79472c8c",
"patch": [
"diff --git a/export.js b/export.js",
"index e69de29..dcd9320 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -0,0 +1,11 @@",
"+export { name1, name2, name3, nameN };",
"+export { variable1 as name1, variable2 as name2, nameN };",
"+export let name1, name2, nameN;",
"+export let name1 = value1, name2 = value2, name3, nameN;",
"+export default namedFunction;",
"+export default function () { };",
"+export default function name1() { };",
"+export { name1 as default };",
"+export * from 'foo';",
"+export { name1, name2, nameN } from 'foo';",
"+export { import1 as name1, import2 as name2, nameN } from 'bar';"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "cd9386b43e1ada367135a44899e2043964488f66"
"shas": "0eb14098d9cfc48fe7ffb44e37c71cb6cb58c878..5e2e89a442ac0f099046b72d57acaa03dc011ed9"
}
,{
"testCaseDescription": "javascript-export-replacement-insert-test",
@ -521,9 +538,40 @@
"filePaths": [
"export.js"
],
"sha1": "cd9386b43e1ada367135a44899e2043964488f66",
"patch": [
"diff --git a/export.js b/export.js",
"index dcd9320..c8b53ff 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,3 +1,25 @@",
"+export { name4, name5, name6, nameZ };",
"+export { variable2 as name2, variable3 as name3, nameY };",
"+export let name3, name4, nameT;",
"+export let name2 = value2, name3 = value3, name4, nameO;",
"+export default otherNamedFunction;",
"+export default function newName1() {};",
"+export default function () {};",
"+export { name2 as statement };",
"+export * from 'baz';",
"+export { name7, name8, nameP } from 'buzz';",
"+export { import6 as name6, import7 as name7, nameB } from 'fizz';",
"+export { name1, name2, name3, nameN };",
"+export { variable1 as name1, variable2 as name2, nameN };",
"+export let name1, name2, nameN;",
"+export let name1 = value1, name2 = value2, name3, nameN;",
"+export default namedFunction;",
"+export default function () { };",
"+export default function name1() { };",
"+export { name1 as default };",
"+export * from 'foo';",
"+export { name1, name2, nameN } from 'foo';",
"+export { import1 as name1, import2 as name2, nameN } from 'bar';",
" export { name1, name2, name3, nameN };",
" export { variable1 as name1, variable2 as name2, nameN };",
" export let name1, name2, nameN;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "5960bd1b757244b4df82cae4bceabe2055ac9c04"
"shas": "5e2e89a442ac0f099046b72d57acaa03dc011ed9..9e81bf04d8f7a930fb0a612fc5230af600c7c5d2"
}
,{
"testCaseDescription": "javascript-export-delete-insert-test",
@ -1254,9 +1302,40 @@
"filePaths": [
"export.js"
],
"sha1": "5960bd1b757244b4df82cae4bceabe2055ac9c04",
"patch": [
"diff --git a/export.js b/export.js",
"index c8b53ff..ad3f21a 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,14 +1,14 @@",
"-export { name4, name5, name6, nameZ };",
"-export { variable2 as name2, variable3 as name3, nameY };",
"-export let name3, name4, nameT;",
"-export let name2 = value2, name3 = value3, name4, nameO;",
"-export default otherNamedFunction;",
"-export default function newName1() {};",
"-export default function () {};",
"-export { name2 as statement };",
"-export * from 'baz';",
"-export { name7, name8, nameP } from 'buzz';",
"-export { import6 as name6, import7 as name7, nameB } from 'fizz';",
"+export { name1, name2, name3, nameN };",
"+export { variable1 as name1, variable2 as name2, nameN };",
"+export let name1, name2, nameN;",
"+export let name1 = value1, name2 = value2, name3, nameN;",
"+export default namedFunction;",
"+export default function () { };",
"+export default function name1() { };",
"+export { name1 as default };",
"+export * from 'foo';",
"+export { name1, name2, nameN } from 'foo';",
"+export { import1 as name1, import2 as name2, nameN } from 'bar';",
" export { name1, name2, name3, nameN };",
" export { variable1 as name1, variable2 as name2, nameN };",
" export let name1, name2, nameN;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "3e09142eeccf41374af934cc1a492e1660a202be"
"shas": "9e81bf04d8f7a930fb0a612fc5230af600c7c5d2..d1bc421a42e531d555179f1135e64e9f19d57095"
}
,{
"testCaseDescription": "javascript-export-replacement-test",
@ -1678,9 +1757,40 @@
"filePaths": [
"export.js"
],
"sha1": "3e09142eeccf41374af934cc1a492e1660a202be",
"patch": [
"diff --git a/export.js b/export.js",
"index ad3f21a..c8b53ff 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,14 +1,14 @@",
"-export { name1, name2, name3, nameN };",
"-export { variable1 as name1, variable2 as name2, nameN };",
"-export let name1, name2, nameN;",
"-export let name1 = value1, name2 = value2, name3, nameN;",
"-export default namedFunction;",
"-export default function () { };",
"-export default function name1() { };",
"-export { name1 as default };",
"-export * from 'foo';",
"-export { name1, name2, nameN } from 'foo';",
"-export { import1 as name1, import2 as name2, nameN } from 'bar';",
"+export { name4, name5, name6, nameZ };",
"+export { variable2 as name2, variable3 as name3, nameY };",
"+export let name3, name4, nameT;",
"+export let name2 = value2, name3 = value3, name4, nameO;",
"+export default otherNamedFunction;",
"+export default function newName1() {};",
"+export default function () {};",
"+export { name2 as statement };",
"+export * from 'baz';",
"+export { name7, name8, nameP } from 'buzz';",
"+export { import6 as name6, import7 as name7, nameB } from 'fizz';",
" export { name1, name2, name3, nameN };",
" export { variable1 as name1, variable2 as name2, nameN };",
" export let name1, name2, nameN;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b1d4ad7f530f1b762b1a4fc4f4d7597666b3f4ec"
"shas": "d1bc421a42e531d555179f1135e64e9f19d57095..61d845cfdc6aaaba0c4fa01fb8ca41f79556ac37"
}
,{
"testCaseDescription": "javascript-export-delete-replacement-test",
@ -2189,9 +2299,55 @@
"filePaths": [
"export.js"
],
"sha1": "b1d4ad7f530f1b762b1a4fc4f4d7597666b3f4ec",
"patch": [
"diff --git a/export.js b/export.js",
"index c8b53ff..281c672 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,25 +1,3 @@",
"-export { name4, name5, name6, nameZ };",
"-export { variable2 as name2, variable3 as name3, nameY };",
"-export let name3, name4, nameT;",
"-export let name2 = value2, name3 = value3, name4, nameO;",
"-export default otherNamedFunction;",
"-export default function newName1() {};",
"-export default function () {};",
"-export { name2 as statement };",
"-export * from 'baz';",
"-export { name7, name8, nameP } from 'buzz';",
"-export { import6 as name6, import7 as name7, nameB } from 'fizz';",
"-export { name1, name2, name3, nameN };",
"-export { variable1 as name1, variable2 as name2, nameN };",
"-export let name1, name2, nameN;",
"-export let name1 = value1, name2 = value2, name3, nameN;",
"-export default namedFunction;",
"-export default function () { };",
"-export default function name1() { };",
"-export { name1 as default };",
"-export * from 'foo';",
"-export { name1, name2, nameN } from 'foo';",
"-export { import1 as name1, import2 as name2, nameN } from 'bar';",
" export { name1, name2, name3, nameN };",
" export { variable1 as name1, variable2 as name2, nameN };",
" export let name1, name2, nameN;",
"@@ -31,3 +9,14 @@ export { name1 as default };",
" export * from 'foo';",
" export { name1, name2, nameN } from 'foo';",
" export { import1 as name1, import2 as name2, nameN } from 'bar';",
"+export { name4, name5, name6, nameZ };",
"+export { variable2 as name2, variable3 as name3, nameY };",
"+export let name3, name4, nameT;",
"+export let name2 = value2, name3 = value3, name4, nameO;",
"+export default otherNamedFunction;",
"+export default function newName1() {};",
"+export default function () {};",
"+export { name2 as statement };",
"+export * from 'baz';",
"+export { name7, name8, nameP } from 'buzz';",
"+export { import6 as name6, import7 as name7, nameB } from 'fizz';"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "ef3fc45439ff4e4a2a491636770addcee77c5796"
"shas": "61d845cfdc6aaaba0c4fa01fb8ca41f79556ac37..06bbce70f8962416f84a41ea00019bfb28b73bf9"
}
,{
"testCaseDescription": "javascript-export-delete-test",
@ -2370,9 +2526,29 @@
"filePaths": [
"export.js"
],
"sha1": "ef3fc45439ff4e4a2a491636770addcee77c5796",
"patch": [
"diff --git a/export.js b/export.js",
"index 281c672..e105ba7 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,14 +1,3 @@",
"-export { name1, name2, name3, nameN };",
"-export { variable1 as name1, variable2 as name2, nameN };",
"-export let name1, name2, nameN;",
"-export let name1 = value1, name2 = value2, name3, nameN;",
"-export default namedFunction;",
"-export default function () { };",
"-export default function name1() { };",
"-export { name1 as default };",
"-export * from 'foo';",
"-export { name1, name2, nameN } from 'foo';",
"-export { import1 as name1, import2 as name2, nameN } from 'bar';",
" export { name4, name5, name6, nameZ };",
" export { variable2 as name2, variable3 as name3, nameY };",
" export let name3, name4, nameT;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b108c428f25f1605b690e84daa6f1c8afbcb8466"
"shas": "06bbce70f8962416f84a41ea00019bfb28b73bf9..d1daa5ccf312ddb7b243f8adf15955fac3df1d63"
}
,{
"testCaseDescription": "javascript-export-delete-rest-test",
@ -2551,7 +2727,24 @@
"filePaths": [
"export.js"
],
"sha1": "b108c428f25f1605b690e84daa6f1c8afbcb8466",
"patch": [
"diff --git a/export.js b/export.js",
"index e105ba7..e69de29 100644",
"--- a/export.js",
"+++ b/export.js",
"@@ -1,11 +0,0 @@",
"-export { name4, name5, name6, nameZ };",
"-export { variable2 as name2, variable3 as name3, nameY };",
"-export let name3, name4, nameT;",
"-export let name2 = value2, name3 = value3, name4, nameO;",
"-export default otherNamedFunction;",
"-export default function newName1() {};",
"-export default function () {};",
"-export { name2 as statement };",
"-export * from 'baz';",
"-export { name7, name8, nameP } from 'buzz';",
"-export { import6 as name6, import7 as name7, nameB } from 'fizz';"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "ddc540ac245ab0b5fd645525c53e4326f07dd253"
"shas": "d1daa5ccf312ddb7b243f8adf15955fac3df1d63..925b73e9fde76236d0b037d687edcc925a5cef9a"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"false.js"
],
"sha1": "04aded71e587d0bada2c50fd567023d9de7f477c",
"patch": [
"diff --git a/false.js b/false.js",
"index e69de29..8a63946 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -0,0 +1 @@",
"+false;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "74941c080527d8accd5c74955fd31110e7be5509"
"shas": "a56c14e19dec2910d36460e4fca6496da46f6240..6b1a30d6be2d43907c3a1faf581db6c9fe6cc88a"
}
,{
"testCaseDescription": "javascript-false-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"false.js"
],
"sha1": "74941c080527d8accd5c74955fd31110e7be5509",
"patch": [
"diff --git a/false.js b/false.js",
"index 8a63946..86574b1 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1 +1,3 @@",
"+return false;",
"+false;",
" false;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "ef20d47afcee8970df0617a652b700e2ea002d85"
"shas": "6b1a30d6be2d43907c3a1faf581db6c9fe6cc88a..122e0fae24e99d4f534bb461d9d5fa2900c70e55"
}
,{
"testCaseDescription": "javascript-false-delete-insert-test",
@ -117,9 +133,19 @@
"filePaths": [
"false.js"
],
"sha1": "ef20d47afcee8970df0617a652b700e2ea002d85",
"patch": [
"diff --git a/false.js b/false.js",
"index 86574b1..7bae7c5 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1,3 +1,3 @@",
"-return false;",
"+false;",
" false;",
" false;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "c5ca8f1fedc05537db6d2a923dc63933396e1bc3"
"shas": "122e0fae24e99d4f534bb461d9d5fa2900c70e55..6d5ec0ada3f32284c9922934304c708333da7e1f"
}
,{
"testCaseDescription": "javascript-false-replacement-test",
@ -163,9 +189,19 @@
"filePaths": [
"false.js"
],
"sha1": "c5ca8f1fedc05537db6d2a923dc63933396e1bc3",
"patch": [
"diff --git a/false.js b/false.js",
"index 7bae7c5..86574b1 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1,3 +1,3 @@",
"-false;",
"+return false;",
" false;",
" false;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "38316340683de061a83087c8aa02ae1abbb37479"
"shas": "6d5ec0ada3f32284c9922934304c708333da7e1f..7291f772ca242bae0a92ab87c1ab6ec2be28d4c1"
}
,{
"testCaseDescription": "javascript-false-delete-replacement-test",
@ -224,9 +260,19 @@
"filePaths": [
"false.js"
],
"sha1": "38316340683de061a83087c8aa02ae1abbb37479",
"patch": [
"diff --git a/false.js b/false.js",
"index 86574b1..85b5be9 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1,3 +1,2 @@",
"-return false;",
"-false;",
" false;",
"+return false;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "3e4d9841d8064e0e35fb4b0fb5a6240ac7f538e6"
"shas": "7291f772ca242bae0a92ab87c1ab6ec2be28d4c1..018e3b49010dd5359d8071f4a856b6ccef409645"
}
,{
"testCaseDescription": "javascript-false-delete-test",
@ -255,9 +301,17 @@
"filePaths": [
"false.js"
],
"sha1": "3e4d9841d8064e0e35fb4b0fb5a6240ac7f538e6",
"patch": [
"diff --git a/false.js b/false.js",
"index 85b5be9..1f328b3 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1,2 +1 @@",
"-false;",
" return false;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "7bee29b9f6ea9ffdaf9141f171828b9e5a3b4e47"
"shas": "018e3b49010dd5359d8071f4a856b6ccef409645..bda912eec94150ac764d032b1243ec8dba01f3f0"
}
,{
"testCaseDescription": "javascript-false-delete-rest-test",
@ -286,7 +340,14 @@
"filePaths": [
"false.js"
],
"sha1": "7bee29b9f6ea9ffdaf9141f171828b9e5a3b4e47",
"patch": [
"diff --git a/false.js b/false.js",
"index 1f328b3..e69de29 100644",
"--- a/false.js",
"+++ b/false.js",
"@@ -1 +0,0 @@",
"-return false;"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "559546b09a86fffc79e8283d8f7567d491c07e90"
"shas": "bda912eec94150ac764d032b1243ec8dba01f3f0..f6dfeb42af9db740677fd60341ea39da711f7c81"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "59c52a0ddb5e652e5b5108d0724541989a6d83aa",
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
"index e69de29..f928287 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -0,0 +1 @@",
"+for (thing in things) { thing(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "29b666fa2472eecf7b9d073a0293fc0d86cbee77"
"shas": "75f87f22428c68545ebb3f876a1b09caf59d75c9..1d91306ffc69509679ae514ecc2a3403dc94aefb"
}
,{
"testCaseDescription": "javascript-for-in-statement-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "29b666fa2472eecf7b9d073a0293fc0d86cbee77",
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
"index f928287..4a482e9 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1 +1,3 @@",
"+for (item in items) { item(); }",
"+for (thing in things) { thing(); }",
" for (thing in things) { thing(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b7391d72e98da90810b11a4ac0ed9027c4ddec08"
"shas": "1d91306ffc69509679ae514ecc2a3403dc94aefb..2f951d1d02db4475f786a87f7077648822ef26d3"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-insert-test",
@ -168,9 +184,19 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "b7391d72e98da90810b11a4ac0ed9027c4ddec08",
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
"index 4a482e9..e949baf 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1,3 +1,3 @@",
"-for (item in items) { item(); }",
"+for (thing in things) { thing(); }",
" for (thing in things) { thing(); }",
" for (thing in things) { thing(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "02ace41153aabc248b4f4c3bbe70edd6cf930933"
"shas": "2f951d1d02db4475f786a87f7077648822ef26d3..31f13f455d1c9d9efae42c7695abae57acf4684a"
}
,{
"testCaseDescription": "javascript-for-in-statement-replacement-test",
@ -265,9 +291,19 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "02ace41153aabc248b4f4c3bbe70edd6cf930933",
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
"index e949baf..4a482e9 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1,3 +1,3 @@",
"-for (thing in things) { thing(); }",
"+for (item in items) { item(); }",
" for (thing in things) { thing(); }",
" for (thing in things) { thing(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "843d56f80f3f9e2e7f2940b4f9382415fb00907c"
"shas": "31f13f455d1c9d9efae42c7695abae57acf4684a..20bf2c4356e71329f5e131bec7be78669308acc8"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-replacement-test",
@ -326,9 +362,19 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "843d56f80f3f9e2e7f2940b4f9382415fb00907c",
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
"index 4a482e9..6b5f12a 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1,3 +1,2 @@",
"-for (item in items) { item(); }",
"-for (thing in things) { thing(); }",
" for (thing in things) { thing(); }",
"+for (item in items) { item(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "0d0d6478c7e57258561455f0ce7b3d3f416f5ae5"
"shas": "20bf2c4356e71329f5e131bec7be78669308acc8..cc6e8abe393b4d3c5e2b919a60c832b78ad0a4cd"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-test",
@ -357,9 +403,17 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "0d0d6478c7e57258561455f0ce7b3d3f416f5ae5",
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
"index 6b5f12a..a3d8882 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1,2 +1 @@",
"-for (thing in things) { thing(); }",
" for (item in items) { item(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "90c8a228bd3e7b8106f7a6461b376abc0055ec37"
"shas": "cc6e8abe393b4d3c5e2b919a60c832b78ad0a4cd..71a7b11ea45ba6cae99bbc5d1bdad0c7eb526a3b"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-rest-test",
@ -388,7 +442,14 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "90c8a228bd3e7b8106f7a6461b376abc0055ec37",
"patch": [
"diff --git a/for-in-statement.js b/for-in-statement.js",
"index a3d8882..e69de29 100644",
"--- a/for-in-statement.js",
"+++ b/for-in-statement.js",
"@@ -1 +0,0 @@",
"-for (item in items) { item(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "d2246a50ed33ef4c748bfdaf80bbf4eb41cc6c57"
"shas": "71a7b11ea45ba6cae99bbc5d1bdad0c7eb526a3b..d1b2bee18a7da4fefa2a4786b2f692fc5795f48c"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "d42f86b317b470d5207108107a9710b5a66b7693",
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
"index e69de29..c467478 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -0,0 +1 @@",
"+for (key in something && i = 0; i < n; i++) { doSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "71e0fa7e41a874b0a5d718c95f074ace55cc9232"
"shas": "1c2dbb18fb6fc930b3d0e6bb31a559a853be5c63..974a2623d96129b8a5eb74659c0040931fe6597a"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "71e0fa7e41a874b0a5d718c95f074ace55cc9232",
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
"index c467478..0147d31 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -1 +1,3 @@",
"+for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
"+for (key in something && i = 0; i < n; i++) { doSomething(); }",
" for (key in something && i = 0; i < n; i++) { doSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "6bac9b37cf2cf093c337582d9de14afa128fed17"
"shas": "974a2623d96129b8a5eb74659c0040931fe6597a..37f9b64351b20f87cdd2d65e794e8b43ea684959"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test",
@ -141,9 +157,19 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "6bac9b37cf2cf093c337582d9de14afa128fed17",
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
"index 0147d31..306fa88 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -1,3 +1,3 @@",
"-for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
"+for (key in something && i = 0; i < n; i++) { doSomething(); }",
" for (key in something && i = 0; i < n; i++) { doSomething(); }",
" for (key in something && i = 0; i < n; i++) { doSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "149bca27f95242b5072ce36f019f298a300f97d3"
"shas": "37f9b64351b20f87cdd2d65e794e8b43ea684959..639c4e9d99aa30a48f0403a42eaf81f85a194e22"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test",
@ -211,9 +237,19 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "149bca27f95242b5072ce36f019f298a300f97d3",
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
"index 306fa88..0147d31 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -1,3 +1,3 @@",
"-for (key in something && i = 0; i < n; i++) { doSomething(); }",
"+for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
" for (key in something && i = 0; i < n; i++) { doSomething(); }",
" for (key in something && i = 0; i < n; i++) { doSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "0a7c075c24681bfa818dffe5a91a41c59d533fcc"
"shas": "639c4e9d99aa30a48f0403a42eaf81f85a194e22..8d475ef797fcd08a47c73f033c305642c4279115"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test",
@ -272,9 +308,19 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "0a7c075c24681bfa818dffe5a91a41c59d533fcc",
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
"index 0147d31..f23fa31 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -1,3 +1,2 @@",
"-for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }",
"-for (key in something && i = 0; i < n; i++) { doSomething(); }",
" for (key in something && i = 0; i < n; i++) { doSomething(); }",
"+for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9ecf6acc87328e9ca74836a467411d20838ceeae"
"shas": "8d475ef797fcd08a47c73f033c305642c4279115..d2051aee8f163a567cf3a5ff4060579795e0a2a1"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-test",
@ -303,9 +349,17 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "9ecf6acc87328e9ca74836a467411d20838ceeae",
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
"index f23fa31..e968160 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -1,2 +1 @@",
"-for (key in something && i = 0; i < n; i++) { doSomething(); }",
" for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "e1f719858553a9e12274fec57ae67a38a67719b3"
"shas": "d2051aee8f163a567cf3a5ff4060579795e0a2a1..068a5eccf07c8be3b3a95d6eceadf7062d7b942d"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test",
@ -334,7 +388,14 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "e1f719858553a9e12274fec57ae67a38a67719b3",
"patch": [
"diff --git a/for-loop-with-in-statement.js b/for-loop-with-in-statement.js",
"index e968160..e69de29 100644",
"--- a/for-loop-with-in-statement.js",
"+++ b/for-loop-with-in-statement.js",
"@@ -1 +0,0 @@",
"-for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "f9d31193b2e0de3664fd90baf4bf0f036eed7805"
"shas": "068a5eccf07c8be3b3a95d6eceadf7062d7b942d..9c2fa1f20200ecb26074ec348c75c13c22138f87"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "f9d31193b2e0de3664fd90baf4bf0f036eed7805",
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
"index e69de29..1ed2754 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -0,0 +1 @@",
"+for (let item of items) { process(item); };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "fdb12c1fe737ef373806b4986172a03007e238c1"
"shas": "9c2fa1f20200ecb26074ec348c75c13c22138f87..c46e44d842f77789f61d1f25221f0449f2d580c5"
}
,{
"testCaseDescription": "javascript-for-of-statement-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "fdb12c1fe737ef373806b4986172a03007e238c1",
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
"index 1ed2754..ab20ded 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -1 +1,3 @@",
"+for (let thing of things) { process(thing); };",
"+for (let item of items) { process(item); };",
" for (let item of items) { process(item); };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "940950f103116ec45a222f21de8cdbcc49f48795"
"shas": "c46e44d842f77789f61d1f25221f0449f2d580c5..1c06836a9dafef9518b54b9409dc10e9e4402666"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-insert-test",
@ -168,9 +184,19 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "940950f103116ec45a222f21de8cdbcc49f48795",
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
"index ab20ded..19561a3 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -1,3 +1,3 @@",
"-for (let thing of things) { process(thing); };",
"+for (let item of items) { process(item); };",
" for (let item of items) { process(item); };",
" for (let item of items) { process(item); };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "682b758ed60acc11b5c83d746f3822ef9e4f870c"
"shas": "1c06836a9dafef9518b54b9409dc10e9e4402666..4c79ce75c12d7e2b77bd33d6f7e4f1d839ee88a8"
}
,{
"testCaseDescription": "javascript-for-of-statement-replacement-test",
@ -265,9 +291,19 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "682b758ed60acc11b5c83d746f3822ef9e4f870c",
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
"index 19561a3..ab20ded 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -1,3 +1,3 @@",
"-for (let item of items) { process(item); };",
"+for (let thing of things) { process(thing); };",
" for (let item of items) { process(item); };",
" for (let item of items) { process(item); };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "661909ac91a22c549b5ba5e40a492192452e9126"
"shas": "4c79ce75c12d7e2b77bd33d6f7e4f1d839ee88a8..cd97645bfe60051a1bbd7a490394b00b6df48a7d"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-replacement-test",
@ -326,9 +362,19 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "661909ac91a22c549b5ba5e40a492192452e9126",
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
"index ab20ded..62db34f 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -1,3 +1,2 @@",
"-for (let thing of things) { process(thing); };",
"-for (let item of items) { process(item); };",
" for (let item of items) { process(item); };",
"+for (let thing of things) { process(thing); };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9e29ecdff2b47416f53acc8e1acd4d51415dedf8"
"shas": "cd97645bfe60051a1bbd7a490394b00b6df48a7d..3fd962ae8d2bc510b50e7e85ef1ce4ad04375eb8"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-test",
@ -357,9 +403,17 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "9e29ecdff2b47416f53acc8e1acd4d51415dedf8",
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
"index 62db34f..5170ce4 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -1,2 +1 @@",
"-for (let item of items) { process(item); };",
" for (let thing of things) { process(thing); };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "bbd14a09e7756c7f89efaaa9bfde692fcd16a0e2"
"shas": "3fd962ae8d2bc510b50e7e85ef1ce4ad04375eb8..821a3c7b8a7b00f8a8ad7967aed163a12f042d10"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-rest-test",
@ -388,7 +442,14 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "bbd14a09e7756c7f89efaaa9bfde692fcd16a0e2",
"patch": [
"diff --git a/for-of-statement.js b/for-of-statement.js",
"index 5170ce4..e69de29 100644",
"--- a/for-of-statement.js",
"+++ b/for-of-statement.js",
"@@ -1 +0,0 @@",
"-for (let thing of things) { process(thing); };"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "a155a2bd652ca5aaa95ea8e31c7eac9662aa07f9"
"shas": "821a3c7b8a7b00f8a8ad7967aed163a12f042d10..0b1a50d075cdb5202c523f929502c24a9fce63ce"
}]

View File

@ -25,9 +25,16 @@
"filePaths": [
"for-statement.js"
],
"sha1": "3b37b1f1ec583cf921f87b304b606d12b388bcd5",
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
"index e69de29..2f51258 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -0,0 +1 @@",
"+for (i = 0, init(); i < 10; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "b871597febfb405a61f6fe7b2bc357fb03aeafe3"
"shas": "eaeb10729b105d290f4091fea5f04c34030bb5a5..40bfcf71debc3d20926578f5d788f319165ccdbb"
}
,{
"testCaseDescription": "javascript-for-statement-replacement-insert-test",
@ -71,9 +78,18 @@
"filePaths": [
"for-statement.js"
],
"sha1": "b871597febfb405a61f6fe7b2bc357fb03aeafe3",
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
"index 2f51258..095241f 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -1 +1,3 @@",
"+for (i = 0, init(); i < 100; i++) { log(i); }",
"+for (i = 0, init(); i < 10; i++) { log(i); }",
" for (i = 0, init(); i < 10; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "9b1d937b78222de41c3c5144f67f075bb43e2c13"
"shas": "40bfcf71debc3d20926578f5d788f319165ccdbb..14acd05cf2f47feba3234c70af8afe86828370ce"
}
,{
"testCaseDescription": "javascript-for-statement-delete-insert-test",
@ -114,9 +130,19 @@
"filePaths": [
"for-statement.js"
],
"sha1": "9b1d937b78222de41c3c5144f67f075bb43e2c13",
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
"index 095241f..9b0e26d 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -1,3 +1,3 @@",
"-for (i = 0, init(); i < 100; i++) { log(i); }",
"+for (i = 0, init(); i < 10; i++) { log(i); }",
" for (i = 0, init(); i < 10; i++) { log(i); }",
" for (i = 0, init(); i < 10; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "c650295f1ecd192eaeae937b7f6175202839a1ea"
"shas": "14acd05cf2f47feba3234c70af8afe86828370ce..26784319f5f567d3017095b6f9d0ca081043b817"
}
,{
"testCaseDescription": "javascript-for-statement-replacement-test",
@ -157,9 +183,19 @@
"filePaths": [
"for-statement.js"
],
"sha1": "c650295f1ecd192eaeae937b7f6175202839a1ea",
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
"index 9b0e26d..095241f 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -1,3 +1,3 @@",
"-for (i = 0, init(); i < 10; i++) { log(i); }",
"+for (i = 0, init(); i < 100; i++) { log(i); }",
" for (i = 0, init(); i < 10; i++) { log(i); }",
" for (i = 0, init(); i < 10; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "92349c8f6582da8eee5c83e7e9d6a7e159b6bd79"
"shas": "26784319f5f567d3017095b6f9d0ca081043b817..5b15f8e9f8b68a8e4f4ba6ec6642a3cb37db7c60"
}
,{
"testCaseDescription": "javascript-for-statement-delete-replacement-test",
@ -218,9 +254,19 @@
"filePaths": [
"for-statement.js"
],
"sha1": "92349c8f6582da8eee5c83e7e9d6a7e159b6bd79",
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
"index 095241f..39af699 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -1,3 +1,2 @@",
"-for (i = 0, init(); i < 100; i++) { log(i); }",
"-for (i = 0, init(); i < 10; i++) { log(i); }",
" for (i = 0, init(); i < 10; i++) { log(i); }",
"+for (i = 0, init(); i < 100; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "ba90f5edb467195216326c4f5da878084a2247c8"
"shas": "5b15f8e9f8b68a8e4f4ba6ec6642a3cb37db7c60..70806220f9fba3804c162aed68cdfcb25c39ff0a"
}
,{
"testCaseDescription": "javascript-for-statement-delete-test",
@ -249,9 +295,17 @@
"filePaths": [
"for-statement.js"
],
"sha1": "ba90f5edb467195216326c4f5da878084a2247c8",
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
"index 39af699..de8ae87 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -1,2 +1 @@",
"-for (i = 0, init(); i < 10; i++) { log(i); }",
" for (i = 0, init(); i < 100; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "c20c08f9fc64911ac52a4f87ca4a60c7fb4c76b5"
"shas": "70806220f9fba3804c162aed68cdfcb25c39ff0a..9d01a0008d001fc966736db7d1583e0415da98fd"
}
,{
"testCaseDescription": "javascript-for-statement-delete-rest-test",
@ -280,7 +334,14 @@
"filePaths": [
"for-statement.js"
],
"sha1": "c20c08f9fc64911ac52a4f87ca4a60c7fb4c76b5",
"patch": [
"diff --git a/for-statement.js b/for-statement.js",
"index de8ae87..e69de29 100644",
"--- a/for-statement.js",
"+++ b/for-statement.js",
"@@ -1 +0,0 @@",
"-for (i = 0, init(); i < 100; i++) { log(i); }"
],
"gitDir": "test/corpus/repos/javascript",
"sha2": "f5dfc0945ffae36e0f9784dcfeb8472344055afc"
"shas": "9d01a0008d001fc966736db7d1583e0415da98fd..10c888c0caabf36cb211a96640afbe435dfad3fb"
}]

Some files were not shown because too many files have changed in this diff Show More