diff --git a/.atom-build.yml b/.atom-build.yml index 52a715550..6daeb5720 100644 --- a/.atom-build.yml +++ b/.atom-build.yml @@ -7,7 +7,5 @@ targets: test: cmd: stack build :integration-test keymap: cmd-u - semantic-git-diff: - cmd: stack build :semantic-git-diff errorMatch: - \n(?/[^:]+):(?\d+):((?\d+):)? diff --git a/.gitmodules b/.gitmodules index 9dd8513be..d0cf67907 100644 --- a/.gitmodules +++ b/.gitmodules @@ -16,3 +16,6 @@ [submodule "test/repos/backbone"] path = test/repos/backbone url = https://github.com/jashkenas/backbone +[submodule "test/corpus/repos/javascript"] + path = test/corpus/repos/javascript + url = https://github.com/rewinfrey/javascript diff --git a/ROADMAP.md b/ROADMAP.md index 3bed09a9e..7aa40435a 100644 --- a/ROADMAP.md +++ b/ROADMAP.md @@ -12,7 +12,7 @@ This is the long form version of our [roadmap project][]. 2. [Semantic diffs][] on .com for C & JavaScript. Q4 2016 or so. - Performance, as above. - - Resilience. A fault in `semantic-git-diff` should not break anything else. + - Resilience. A fault in `semantic-diff` should not break anything else. - Metrics. We need to know how it’s behaving in the wild to know what to do about it. This also includes operational metrics such as health checks. ## Follow-up things: diff --git a/app/GenerateTestCases.hs b/app/GenerateTestCases.hs new file mode 100644 index 000000000..cd18d0961 --- /dev/null +++ b/app/GenerateTestCases.hs @@ -0,0 +1,246 @@ +{-# LANGUAGE LambdaCase #-} +module Main where + +import Arguments +import Control.Exception +import Data.Aeson +import Data.Aeson.Encode.Pretty +import Data.Map.Strict as Map +import qualified Data.ByteString.Lazy as DL +import qualified Data.ByteString.Char8 as DC +import Data.String +import qualified Data.Text as DT +import JSONTestCase +import qualified Prelude +import Prologue +import SemanticDiff (fetchDiffs) +import System.FilePath.Glob +import System.Process +import qualified Data.String.Utils as DSUtils +import Options.Applicative hiding ((<>)) +import qualified Options.Applicative as O +import qualified Renderer as R + +data GeneratorArgs = GeneratorArgs { generateResults :: Bool } deriving (Show) + +generatorArgs :: Parser GeneratorArgs +generatorArgs = GeneratorArgs <$> switch ( long "generate-results" O.<> short 'g' O.<> help "Use generated expected results for new JSON test cases (rather than defaulting to an empty \"\")" ) + +options :: ParserInfo GeneratorArgs +options = info (helper <*> generatorArgs) (fullDesc O.<> progDesc "Auto-generate JSON test cases" O.<> header "JSON Test Case Generator") + +main :: IO () +main = do + opts <- execParser options + generatorFilePaths <- runFetchGeneratorFiles + unparsedGeneratorCases <- traverse DL.readFile generatorFilePaths + let parsedGeneratorCases = eitherDecode <$> unparsedGeneratorCases :: [Either String [JSONMetaRepo]] + traverse_ (handleGeneratorCases opts generatorFilePaths) parsedGeneratorCases + where handleGeneratorCases :: GeneratorArgs -> [FilePath] -> Either String [JSONMetaRepo] -> IO () + handleGeneratorCases opts generatorFilePaths parsedGeneratorCase = + case parsedGeneratorCase of + Left err -> Prelude.putStrLn $ "An error occurred: " <> err + Right metaTestCases -> do + traverse_ (runGenerator opts) metaTestCases + traverse_ runMoveGeneratorFile generatorFilePaths + +-- | Finds all JSON files within the generators directory. +runFetchGeneratorFiles :: IO [FilePath] +runFetchGeneratorFiles = globDir1 (compile "*.json") "test/corpus/generators" + +-- | First initialize the git submodule repository where commits will be made for the given metaRepo and its syntaxes. +-- | Second generate the commits for each syntax and generate the associated JSONTestCase objects. +-- | Finally push the generated commits to the submodule's remote repository. +runGenerator :: GeneratorArgs -> JSONMetaRepo -> IO () +runGenerator opts metaRepo@JSONMetaRepo{..} = do + runSetupGitRepo metaRepo + runCommitsAndTestCasesGeneration opts metaRepo + runUpdateGitRemote repoPath + +-- | Upon successful test case generation for a generator file, move the file to the generated directory. +-- | This prevents subsequence runs of the test generator from duplicating test cases and adding extraneous +-- | commits to the git submodule. +runMoveGeneratorFile :: FilePath -> IO () +runMoveGeneratorFile filePath = do + let updatedPath = DT.unpack $ DT.replace (DT.pack "generators") (DT.pack "generated") (DT.pack filePath) + Prelude.putStrLn updatedPath + _ <- readCreateProcess (shell $ "mv " <> filePath <> " " <> updatedPath) "" + return () + +-- | Initializes a new git repository and adds it as a submodule to the semantic-diff git index. +-- | This repository contains the commits associated with the given JSONMetaRepo's syntax examples. +runSetupGitRepo :: JSONMetaRepo -> IO () +runSetupGitRepo JSONMetaRepo{..} = do + runInitializeRepo repoUrl repoPath + runAddSubmodule repoUrl repoPath + +-- | Performs the system calls for initializing the git repository. +-- | If the git repository already exists, the operation will result in an error, +-- | but will not prevent successful completion of the test case generation. +runInitializeRepo :: String -> FilePath -> IO () +runInitializeRepo repoUrl repoPath = do + result <- try $ readCreateProcess (shell $ mkDirCommand repoPath) "" + case (result :: Either Prelude.IOError String) of + Left error -> Prelude.putStrLn $ "Creating the repository directory at " <> repoPath <> " failed with: " <> show error <> ". " <> "Possible reason: repository already initialized. \nProceeding to the next step." + Right _ -> do + _ <- executeCommand repoPath (initializeRepoCommand repoUrl) + Prelude.putStrLn $ "Repository directory successfully initialized for " <> repoPath <> "." + +-- | Git repositories generated as a side-effect of generating tests cases are +-- | added to semantic-diff's git index as submodules. If the submodule initialization +-- | fails (usually because the submodule was already initialized), operations will +-- | continue. +runAddSubmodule :: String -> FilePath -> IO () +runAddSubmodule repoUrl repoPath = do + result <- try $ readCreateProcess (shell $ addSubmoduleCommand repoUrl repoPath) "" + case (result :: Either Prelude.IOError String) of + Left error -> Prelude.putStrLn $ "Initializing the submodule repository at " <> repoPath <> " failed with: " <> show error <> ". " <> "Possible reason: submodule already initialized. \nProceeding to the next step." + _ -> Prelude.putStrLn $ "Submodule successfully initialized for " <> repoPath <> "." + +-- | Performs the system calls for generating the commits and test cases. +-- | Also appends the JSONTestCases generated to the test case file defined by +-- | the syntaxes. +runCommitsAndTestCasesGeneration :: GeneratorArgs -> JSONMetaRepo -> IO () +runCommitsAndTestCasesGeneration opts JSONMetaRepo{..} = + for_ syntaxes generate + where generate :: JSONMetaSyntax -> IO () + generate metaSyntax = do + _ <- runInitialCommitForSyntax repoPath metaSyntax + runSetupTestCaseFile metaSyntax + runCommitAndTestCaseGeneration opts language repoPath metaSyntax + runCloseTestCaseFile metaSyntax + +-- | For a syntax, we want the initial commit to be an empty file. +-- | This function performs a touch and commits the empty file. +runInitialCommitForSyntax :: FilePath -> JSONMetaSyntax -> IO () +runInitialCommitForSyntax repoPath JSONMetaSyntax{..} = do + Prelude.putStrLn $ "Generating initial commit for " <> syntax <> " syntax." + result <- try . executeCommand repoPath $ touchCommand repoFilePath <> commitCommand syntax "Initial commit" + case ( result :: Either Prelude.IOError String) of + Left error -> Prelude.putStrLn $ "Initializing the " <> repoFilePath <> " failed with: " <> show error <> ". " <> "Possible reason: file already initialized. \nProceeding to the next step." + Right _ -> pure () + +-- | Initializes the test case file where JSONTestCase examples are written to. +-- | This manually inserts a "[" to open a JSON array. +runSetupTestCaseFile :: JSONMetaSyntax -> IO () +runSetupTestCaseFile metaSyntax = do + Prelude.putStrLn $ "Opening " <> testCaseFilePath metaSyntax + DL.writeFile (testCaseFilePath metaSyntax) "[" + +-- | For each command constructed for a given metaSyntax, execute the system commands. +runCommitAndTestCaseGeneration :: GeneratorArgs -> String -> FilePath -> JSONMetaSyntax -> IO () +runCommitAndTestCaseGeneration opts language repoPath metaSyntax@JSONMetaSyntax{..} = + traverse_ (runGenerateCommitAndTestCase opts language repoPath) (commands metaSyntax) + +maybeMapSummary :: [R.Output] -> [Maybe (Map Text (Map Text [Value]))] +maybeMapSummary = fmap $ \case + R.SummaryOutput output -> Just output + _ -> Nothing + +-- | This function represents the heart of the test case generation. It keeps track of +-- | the git shas prior to running a command, fetches the git sha after a command, so that +-- | JSONTestCase objects can be created. Finally, it appends the created JSONTestCase +-- | object to the test case file. +runGenerateCommitAndTestCase :: GeneratorArgs -> String -> FilePath -> (JSONMetaSyntax, String, String, String) -> IO () +runGenerateCommitAndTestCase opts language repoPath (JSONMetaSyntax{..}, description, seperator, command) = do + Prelude.putStrLn $ "Executing " <> syntax <> " " <> description <> " commit." + beforeSha <- executeCommand repoPath getLastCommitShaCommand + _ <- executeCommand repoPath command + afterSha <- executeCommand repoPath getLastCommitShaCommand + + (summaryChanges, summaryErrors) <- runMaybeSummaries beforeSha afterSha repoPath repoFilePath opts + + let jsonTestCase = encodePretty JSONTestCase { + gitDir = extractGitDir repoPath, + testCaseDescription = language <> "-" <> syntax <> "-" <> description <> "-" <> "test", + filePaths = [repoFilePath], + sha1 = beforeSha, + sha2 = afterSha, + expectedResult = Map.fromList [ + ("changes", fromMaybe (Map.singleton mempty mempty) summaryChanges), + ("errors", fromMaybe (Map.singleton mempty mempty) summaryErrors) + ] + } + + Prelude.putStrLn $ "Generating test case for " <> language <> ": " <> syntax <> " " <> description <> "." + + DL.appendFile testCaseFilePath $ jsonTestCase <> DL.fromStrict (DC.pack seperator) + where extractGitDir :: String -> String + extractGitDir fullRepoPath = DC.unpack $ snd $ DC.breakSubstring (DC.pack "test") (DC.pack fullRepoPath) + +-- | Conditionally generate the diff summaries for the given shas and file path based +-- | on the -g | --generate flag. By default diff summaries are not generated when +-- | constructing test cases, and the tuple (Nothing, Nothing) is returned. +runMaybeSummaries :: String -> String -> FilePath -> FilePath -> GeneratorArgs -> IO (Maybe (Map Text [Value]), Maybe (Map Text [Value])) +runMaybeSummaries beforeSha afterSha repoPath repoFilePath GeneratorArgs{..} + | generateResults = do + diffs <- fetchDiffs $ args repoPath beforeSha afterSha [repoFilePath] R.Summary + let headResult = Prelude.head $ maybeMapSummary diffs + let changes = fromMaybe (fromList [("changes", mempty)]) headResult ! "changes" + let errors = fromMaybe (fromList [("errors", mempty)]) headResult ! "errors" + return (Just changes, Just errors) + | otherwise = return (Nothing, Nothing) + +-- | Commands represent the various combination of patches (insert, delete, replacement) +-- | for a given syntax. +commands :: JSONMetaSyntax -> [(JSONMetaSyntax, String, String, String)] +commands 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") + ] + where commaSeperator = "\n," + spaceSeperator = "" + +-- | Pushes git commits to the submodule repository's remote. +runUpdateGitRemote :: FilePath -> IO () +runUpdateGitRemote repoPath = do + Prelude.putStrLn "Updating git remote." + _ <- executeCommand repoPath pushToGitRemoteCommand + Prelude.putStrLn "Successfully updated git remote." + +-- | Closes the JSON array and closes the test case file. +runCloseTestCaseFile :: JSONMetaSyntax -> IO () +runCloseTestCaseFile metaSyntax = do + Prelude.putStrLn $ "Closing " <> testCaseFilePath metaSyntax + DL.appendFile (testCaseFilePath metaSyntax) "]\n" + +initializeRepoCommand :: String -> String +initializeRepoCommand repoUrl = "rm -rf *; rm -rf .git; git init .; git remote add origin " <> repoUrl <> ";" + +addSubmoduleCommand :: String -> FilePath -> String +addSubmoduleCommand repoUrl repoPath = "git submodule add " <> repoUrl <> " " <> " ./" <> repoPath <> ";" + +getLastCommitShaCommand :: String +getLastCommitShaCommand = "git log --pretty=format:\"%H\" -n 1;" + +touchCommand :: FilePath -> String +touchCommand repoFilePath = "touch " <> repoFilePath <> ";" + +-- | In order to correctly record syntax examples that include backticks (like JavaScript template strings) +-- | we must first escape them for bash (due to the use of the `echo` system command). Additionally, +-- | we must also escape the escape character `\` in Haskell, hence the double `\\`. +fileWriteCommand :: FilePath -> String -> String +fileWriteCommand 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 <> "\"" <> ";" + +removeCommand :: FilePath -> String +removeCommand repoFilePath = "rm " <> repoFilePath <> ";" + +pushToGitRemoteCommand :: String +pushToGitRemoteCommand = "git push origin HEAD;" + +mkDirCommand :: FilePath -> String +mkDirCommand repoPath = "mkdir " <> repoPath <> ";" + +executeCommand :: FilePath -> String -> IO String +executeCommand repoPath command = readCreateProcess (shell command) { cwd = Just repoPath } "" diff --git a/app/Main.hs b/app/Main.hs new file mode 100644 index 000000000..f913510b8 --- /dev/null +++ b/app/Main.hs @@ -0,0 +1,3 @@ +module Main (main) +where +import SemanticDiff (main) diff --git a/bench/Main.hs b/bench/Main.hs index 236835536..67c27a3eb 100644 --- a/bench/Main.hs +++ b/bench/Main.hs @@ -10,11 +10,16 @@ import Patch import Prologue import SES import Test.QuickCheck hiding (Fixed) +import Arguments +import SemanticDiff (fetchDiffs) +import qualified Renderer as R +import qualified SemanticDiffPar +import System.Directory (makeAbsolute) main :: IO () main = do benchmarks <- sequenceA [ generativeBenchmarkWith "ses" 10 arbitrarySESInputs (uncurry ((*) `on` length)) (nf (uncurry benchmarkSES)) ] - defaultMain benchmarks + defaultMain (syncAsyncBenchmark : benchmarks) where arbitrarySESInputs = (,) <$> sized (`vectorOf` arbitrary) <*> sized (`vectorOf` arbitrary) benchmarkSES :: [String] -> [String] -> [Either String (Patch String)] @@ -39,3 +44,31 @@ generativeBenchmarkWith name n generator metric benchmark = do let measurement = metric input pure $! (measurement, bench (show measurement) (benchmark input)) defaultSize = 100 + +syncAsyncBenchmark :: Benchmark +syncAsyncBenchmark = + bgroup "async vs par" [ + bench "async" . whnfIO $ SemanticDiff.fetchDiffs =<< theArgs, + bench "par" . whnfIO $ SemanticDiffPar.fetchDiffs =<< theArgs + ] + +theArgs :: IO Arguments +theArgs = do + jqueryPath <- makeAbsolute "test/repos/jquery" + pure $ args jqueryPath sha1 sha2 files R.Patch + where + sha1 = "70526981916945dc4093e116a3de61b1777d4718" + sha2 = "e5ffcb0838c894e26f4ff32dfec162cf624d8d7d" + files = [ + "src/manipulation/getAll.js", + "src/manipulation/support.js", + "src/manipulation/wrapMap.js", + "src/offset.js", + "test/unit/css.js", + "test/unit/deferred.js", + "test/unit/deprecated.js", + "test/unit/effects.js", + "test/unit/event.js", + "test/unit/offset.js", + "test/unit/wrap.js" + ] diff --git a/bench/SemanticDiffPar.hs b/bench/SemanticDiffPar.hs new file mode 100644 index 000000000..cfa440087 --- /dev/null +++ b/bench/SemanticDiffPar.hs @@ -0,0 +1,12 @@ +module SemanticDiffPar where + +import Arguments +import qualified Control.Monad.Par.IO as ParIO +import Control.Monad.Reader +import qualified Data.Text as T +import Prologue +import qualified Renderer as R +import SemanticDiff + +fetchDiffs :: Arguments -> IO [T.Text] +fetchDiffs args@Arguments{..} = pure . pure . R.concatOutputs =<< (ParIO.runParIO . liftIO $ for filePaths (fetchDiff args)) diff --git a/semantic-diff.cabal b/semantic-diff.cabal index 1f486a705..5e98dffcb 100644 --- a/semantic-diff.cabal +++ b/semantic-diff.cabal @@ -1,5 +1,5 @@ name: semantic-diff -version: 0.1.0 +version: 0.2.0 synopsis: Initial project template from stack description: Please see README.md homepage: http://github.com/github/semantic-diff#readme @@ -20,13 +20,14 @@ library , Data.Align.Generic , Data.Bifunctor.Join.Arbitrary , Data.Functor.Both - , Data.RandomWalkSimilarity - , Data.Record , Data.Mergeable , Data.Mergeable.Generic + , Data.RandomWalkSimilarity + , Data.Record , Diff , Diff.Arbitrary , Diffing + , DiffSummary , Info , Interpreter , Language @@ -36,12 +37,15 @@ library , Parser , Patch , Patch.Arbitrary + , Paths_semantic_diff + , Prologue , Range , Renderer , Renderer.JSON , Renderer.Patch , Renderer.Split , Renderer.Summary + , SemanticDiff , SES , Source , SourceSpan @@ -50,58 +54,94 @@ library , Term , Term.Arbitrary , TreeSitter - , DiffSummary - , Prologue - , Paths_semantic_diff - build-depends: aeson - , base >= 4.8 && < 5 + build-depends: base >= 4.8 && < 5 + , aeson + , async-pool , bifunctors , blaze-html , blaze-markup , bytestring , cmark + , comonad , containers , directory , dlist , filepath + , free + , gitlib + , gitlib-libgit2 + , gitrev , hashable , kdt - , mtl , MonadRandom + , mtl + , optparse-applicative , pointed + , protolude , QuickCheck >= 2.8.1 + , quickcheck-instances , quickcheck-text + , recursion-schemes + , regex-compat , semigroups , text >= 1.2.1.3 , text-icu , these , tree-sitter-parsers , vector - , recursion-schemes - , free - , comonad - , protolude , wl-pprint-text - , quickcheck-instances default-language: Haskell2010 default-extensions: DeriveFunctor, DeriveFoldable, DeriveTraversable, DeriveGeneric, FlexibleContexts, FlexibleInstances, OverloadedStrings, NoImplicitPrelude, RecordWildCards, LambdaCase ghc-options: -Wall -fno-warn-name-shadowing -O2 -fprof-auto -j +executable semantic-diff + hs-source-dirs: app + main-is: Main.hs + ghc-options: -threaded -rtsopts -with-rtsopts=-N -static -j -O2 -pgml=script/g++ + cc-options: -DU_STATIC_IMPLEMENTATION=1 + cpp-options: -DU_STATIC_IMPLEMENTATION=1 + build-depends: base + , semantic-diff + default-language: Haskell2010 + default-extensions: FlexibleInstances, OverloadedStrings, NoImplicitPrelude, RecordWildCards + +executable generate-test-cases + hs-source-dirs: app, test + main-is: GenerateTestCases.hs + ghc-options: -threaded -rtsopts -with-rtsopts=-N -static -j -pgml=script/g++ + cc-options: -DU_STATIC_IMPLEMENTATION=1 + cpp-options: -DU_STATIC_IMPLEMENTATION=1 + other-modules: JSONTestCase + build-depends: base + , aeson + , aeson-pretty + , bytestring + , containers + , Glob + , MissingH + , optparse-applicative + , process + , semantic-diff + , text >= 1.2.1.3 + default-language: Haskell2010 + default-extensions: DeriveFunctor, DeriveFoldable, DeriveTraversable, DeriveGeneric, FlexibleContexts, FlexibleInstances, OverloadedStrings, NoImplicitPrelude, RecordWildCards, LambdaCase + benchmark semantic-diff-bench type: exitcode-stdio-1.0 main-is: Main.hs hs-source-dirs: bench + other-modules: SemanticDiffPar build-depends: base - , bifunctors , criterion + , directory + , monad-par + , mtl , QuickCheck >= 2.8.1 - , quickcheck-text - , recursion-schemes , semantic-diff - , these + , text >= 1.2.1.3 ghc-options: -threaded -rtsopts -with-rtsopts=-N -j -O2 -static -pgml=script/g++ default-language: Haskell2010 - default-extensions: OverloadedStrings, NoImplicitPrelude + default-extensions: FlexibleInstances, OverloadedStrings, NoImplicitPrelude, RecordWildCards test-suite test type: exitcode-stdio-1.0 @@ -120,15 +160,13 @@ test-suite test , TermSpec build-depends: base , bifunctors - , bytestring - , containers , deepseq - , dlist , filepath - , free , Glob , hspec >= 2.1.10 + , hspec-expectations-pretty-diff , mtl + , protolude , QuickCheck >= 2.8.1 , quickcheck-text , recursion-schemes >= 4.1 @@ -136,13 +174,28 @@ test-suite test , text >= 1.2.1.3 , these , vector - , wl-pprint-text - , protolude - , hspec-expectations-pretty-diff ghc-options: -threaded -rtsopts -with-rtsopts=-N -j -pgml=script/g++ default-language: Haskell2010 default-extensions: DeriveFunctor, DeriveGeneric, FlexibleContexts, FlexibleInstances, OverloadedStrings, NoImplicitPrelude, RecordWildCards +test-suite integration-test + type: exitcode-stdio-1.0 + hs-source-dirs: test + main-is: SpecIntegration.hs + other-modules: SemanticGitDiffSpec + , JSONTestCase + build-depends: base + , aeson + , bytestring + , containers + , Glob + , hspec >= 2.1.10 + , hspec-expectations-pretty-diff + , semantic-diff + ghc-options: -threaded -rtsopts -with-rtsopts=-N -j -pgml=script/g++ + default-language: Haskell2010 + default-extensions: DeriveGeneric, FlexibleInstances, OverloadedStrings, NoImplicitPrelude, RecordWildCards + source-repository head type: git location: https://github.com/github/semantic-diff diff --git a/src/DiffSummary.hs b/src/DiffSummary.hs index f3d7a21fe..746f58316 100644 --- a/src/DiffSummary.hs +++ b/src/DiffSummary.hs @@ -149,8 +149,7 @@ toLeafInfos err@ErrorInfo{..} = pure $ ErrorSummary (pretty err) errorSpan -- Returns a text representing a specific term given a source and a term. toTermName :: forall leaf fields. (HasCategory leaf, HasField fields Category, HasField fields Range) => Source Char -> SyntaxTerm leaf fields -> Text toTermName source term = case unwrap term of - S.AnonymousFunction maybeParams _ -> "anonymous" <> maybe "" toParams maybeParams <> " function" - where toParams ps = " (" <> termNameFromSource ps <> ")" + S.AnonymousFunction params _ -> "anonymous" <> paramsToArgNames params <> " function" S.Fixed children -> fromMaybe "branch" $ (toCategoryName . category) . extract <$> head children S.Indexed children -> fromMaybe "branch" $ (toCategoryName . category) . extract <$> head children Leaf leaf -> toCategoryName leaf @@ -162,7 +161,7 @@ toTermName source term = case unwrap term of (S.FunctionCall{}, _) -> toTermName' base <> "()." <> toTermName' property (_, S.FunctionCall{}) -> toTermName' base <> "." <> toTermName' property <> "()" (_, _) -> toTermName' base <> "." <> toTermName' property - S.MethodCall targetId methodId methodParams -> toTermName' targetId <> sep <> toTermName' methodId <> "(" <> intercalate ", " (toArgName <$> methodParams) <> ")" + S.MethodCall targetId methodId methodParams -> toTermName' targetId <> sep <> toTermName' methodId <> paramsToArgNames methodParams where sep = case unwrap targetId of S.FunctionCall{} -> "()." _ -> "." @@ -205,6 +204,7 @@ toTermName source term = case unwrap term of termNameFromSource term = termNameFromRange (range term) termNameFromRange range = toText $ Source.slice range source range = characterRange . extract + paramsToArgNames params = "(" <> intercalate ", " (toArgName <$> params) <> ")" toArgName :: SyntaxTerm leaf fields -> Text toArgName arg = case identifiable arg of Identifiable arg -> toTermName' arg diff --git a/src/Language/JavaScript.hs b/src/Language/JavaScript.hs index 070683e41..811f09d16 100644 --- a/src/Language/JavaScript.hs +++ b/src/Language/JavaScript.hs @@ -69,11 +69,9 @@ termConstructor source sourceSpan name range children _ | name `elem` forStatements, Just (exprs, body) <- unsnoc children -> S.For exprs body _ | name `elem` operators -> S.Operator children _ | name `elem` functions -> case children of - [ body ] -> S.AnonymousFunction Nothing body - [ idOrParams, body] -> case unwrap idOrParams of - S.Leaf _ -> S.Function idOrParams Nothing body - _ -> S.AnonymousFunction (Just idOrParams) body - [ id, params, body ] -> S.Function id (Just params) body + [ body ] -> S.AnonymousFunction [] body + [ params, body ] -> S.AnonymousFunction (toList (unwrap params)) body + [ id, params, body ] -> S.Function id (toList (unwrap params)) body _ -> S.Indexed children (_, []) -> S.Leaf . toText $ slice range source _ -> S.Indexed children diff --git a/src/SemanticDiff.hs b/src/SemanticDiff.hs new file mode 100644 index 000000000..3da4eb231 --- /dev/null +++ b/src/SemanticDiff.hs @@ -0,0 +1,156 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# OPTIONS_GHC -fno-warn-warnings-deprecations -fno-warn-incomplete-patterns #-} +module SemanticDiff (main, fetchDiff, fetchDiffs) where + +import Arguments +import Prologue hiding ((<>), fst, snd) +import Data.String +import Data.Functor.Both +import Data.Version (showVersion) +import Text.Regex +import Diffing +import Git.Libgit2 +import Git.Repository +import Git.Blob +import Git.Types +import Git.Libgit2.Backend +import Options.Applicative hiding (action) +import System.Timeout as Timeout +import Data.List ((\\)) +import qualified Diffing as D +import qualified Git +import qualified Paths_semantic_diff as Library (version) +import qualified Renderer as R +import qualified Source +import qualified Control.Concurrent.Async.Pool as Async +import GHC.Conc (numCapabilities) +import Development.GitRev + +main :: IO () +main = do + args@Arguments{..} <- programArguments =<< execParser argumentsParser + case diffMode of + PathDiff paths -> diffPaths args paths + CommitDiff -> diffCommits args + +-- | A parser for the application's command-line arguments. +argumentsParser :: ParserInfo CmdLineOptions +argumentsParser = info (version <*> helper <*> argumentsP) + (fullDesc <> progDesc "Set the GIT_DIR environment variable to specify the git repository. Set GIT_ALTERNATE_OBJECT_DIRECTORIES to specify location of alternates." + <> header "semantic-diff - Show semantic changes between commits") + where + argumentsP :: Parser CmdLineOptions + argumentsP = CmdLineOptions + <$> (flag R.Split R.Patch (long "patch" <> help "output a patch(1)-compatible diff") + <|> flag R.Split R.JSON (long "json" <> help "output a json diff") + <|> flag' R.Split (long "split" <> help "output a split diff") + <|> flag' R.Summary (long "summary" <> help "output a diff summary")) + <*> optional (option auto (long "timeout" <> help "timeout for per-file diffs in seconds, defaults to 7 seconds")) + <*> optional (strOption (long "output" <> short 'o' <> help "output directory for split diffs, defaults to stdout if unspecified")) + <*> switch (long "no-index" <> help "compare two paths on the filesystem") + <*> some (argument (eitherReader parseShasAndFiles) (metavar "SHA_A..SHAB FILES...")) + where + parseShasAndFiles :: String -> Either String ExtraArg + parseShasAndFiles s = case matchRegex regex s of + Just ["", sha2] -> Right . ShaPair $ both Nothing (Just sha2) + Just [sha1, sha2] -> Right . ShaPair $ Just <$> both sha1 sha2 + _ -> Right $ FileArg s + where regex = mkRegexWithOpts "([0-9a-f]{40})\\.\\.([0-9a-f]{40})" True False + +versionString :: String +versionString = "semantic-diff version " <> showVersion Library.version <> " (" <> $(gitHash) <> ")" + +version :: Parser (a -> a) +version = infoOption versionString (long "version" <> short 'V' <> help "output the version of the program") + +-- | Compare changes between two commits. +diffCommits :: Arguments -> IO () +diffCommits args@Arguments{..} = do + ts <- Timeout.timeout timeoutInMicroseconds (fetchDiffs args) + writeToOutput output (maybe mempty R.concatOutputs ts) + +-- | Compare two paths on the filesystem (compariable to git diff --no-index). +diffPaths :: Arguments -> Both FilePath -> IO () +diffPaths args@Arguments{..} paths = do + sources <- sequence $ readAndTranscodeFile <$> paths + let sourceBlobs = Source.SourceBlob <$> sources <*> pure mempty <*> paths <*> pure (Just Source.defaultPlainBlob) + D.printDiff (parserForFilepath (fst paths)) (diffArgs args) sourceBlobs + where + diffArgs Arguments{..} = R.DiffArguments { format = format, output = output } + +fetchDiffs :: Arguments -> IO [R.Output] +fetchDiffs args@Arguments{..} = do + paths <- case(filePaths, shaRange) of + ([], Join (Just a, Just b)) -> pathsToDiff args (both a b) + (ps, _) -> pure ps + + Async.withTaskGroup numCapabilities $ \p -> + Async.mapTasks p (fetchDiff args <$> paths) + +fetchDiff :: Arguments -> FilePath -> IO R.Output +fetchDiff args@Arguments{..} filepath = withRepository lgFactory gitDir $ do + repo <- getRepository + for_ alternateObjectDirs (liftIO . odbBackendAddPath repo . toS) + lift $ runReaderT (fetchDiff' args filepath) repo + +fetchDiff' :: Arguments -> FilePath -> ReaderT LgRepo IO R.Output +fetchDiff' Arguments{..} filepath = do + sourcesAndOids <- sequence $ traverse (getSourceBlob filepath) <$> shaRange + + let sources = fromMaybe (Source.emptySourceBlob filepath) <$> sourcesAndOids + let sourceBlobs = Source.idOrEmptySourceBlob <$> sources + + let textDiff = D.textDiff (parserForFilepath filepath) diffArguments sourceBlobs + text <- liftIO $ Timeout.timeout timeoutInMicroseconds textDiff + + truncatedPatch <- liftIO $ D.truncatedDiff diffArguments sourceBlobs + pure $ fromMaybe truncatedPatch text + where + diffArguments = R.DiffArguments { format = format, output = output } + +pathsToDiff :: Arguments -> Both String -> IO [FilePath] +pathsToDiff Arguments{..} shas = withRepository lgFactory gitDir $ do + repo <- getRepository + for_ alternateObjectDirs (liftIO . odbBackendAddPath repo . toS) + lift $ runReaderT (pathsToDiff' shas) repo + +-- | Returns a list of relative file paths that have changed between the given commit shas. +pathsToDiff' :: Both String -> ReaderT LgRepo IO [FilePath] +pathsToDiff' shas = do + entries <- blobEntriesToDiff shas + pure $ (\(p, _, _) -> toS p) <$> entries + +-- | Returns a list of blob entries that have changed between the given commits shas. +blobEntriesToDiff :: Both String -> ReaderT LgRepo IO [(TreeFilePath, Git.BlobOid LgRepo, BlobKind)] +blobEntriesToDiff shas = do + a <- blobEntries (fst shas) + b <- blobEntries (snd shas) + pure $ (a \\ b) <> (b \\ a) + where blobEntries sha = treeForCommitSha sha >>= treeBlobEntries + +-- | Returns a Git.Tree for a commit sha +treeForCommitSha :: String -> ReaderT LgRepo IO (Git.Tree LgRepo) +treeForCommitSha sha = do + object <- parseObjOid (toS sha) + commit <- lookupCommit object + lookupTree (commitTree commit) + +-- | Returns a SourceBlob given a relative file path, and the sha to look up. +getSourceBlob :: FilePath -> String -> ReaderT LgRepo IO Source.SourceBlob +getSourceBlob path sha = do + tree <- treeForCommitSha sha + entry <- treeEntry tree (toS path) + (bytestring, oid, mode) <- case entry of + Nothing -> pure (mempty, mempty, Nothing) + Just (BlobEntry entryOid entryKind) -> do + blob <- lookupBlob entryOid + let (BlobString s) = blobContents blob + let oid = renderObjOid $ blobOid blob + pure (s, oid, Just entryKind) + s <- liftIO $ transcode bytestring + pure $ Source.SourceBlob s (toS oid) path (toSourceKind <$> mode) + where + toSourceKind :: Git.BlobKind -> Source.SourceKind + toSourceKind (Git.PlainBlob mode) = Source.PlainBlob mode + toSourceKind (Git.ExecutableBlob mode) = Source.ExecutableBlob mode + toSourceKind (Git.SymlinkBlob mode) = Source.SymlinkBlob mode diff --git a/src/Syntax.hs b/src/Syntax.hs index 229499422..15b00b788 100644 --- a/src/Syntax.hs +++ b/src/Syntax.hs @@ -22,9 +22,9 @@ data Syntax a f -- | A ternary has a condition, a true case and a false case | Ternary { ternaryCondition :: f, ternaryCases :: [f] } -- | An anonymous function has a list of expressions and params. - | AnonymousFunction { params :: Maybe f, expressions :: f } + | AnonymousFunction { params :: [f], expressions :: f } -- | A function has a list of expressions. - | Function { id :: f, params :: Maybe f, expressions :: f } + | Function { id :: f, params :: [f], expressions :: f } -- | An assignment has an identifier where f can be a member access, and the value is another syntax element (function call, leaf, etc.) | Assignment { assignmentId :: f, value :: f } -- | A math assignment represents expressions whose operator classifies as mathy (e.g. += or *=). diff --git a/src/TreeSitter.hs b/src/TreeSitter.hs index 7ca9ca8f0..54dfdf003 100644 --- a/src/TreeSitter.hs +++ b/src/TreeSitter.hs @@ -21,7 +21,7 @@ import Info -- | Returns a TreeSitter parser for the given language and TreeSitter grammar. treeSitterParser :: Language -> Ptr TS.Language -> Parser (Syntax.Syntax Text) (Record '[Range, Category, SourceSpan]) treeSitterParser language grammar blob = do - document <- ts_document_make + document <- ts_document_new ts_document_set_language document grammar withCString (toString $ source blob) (\source -> do ts_document_set_input_string document source diff --git a/test/JSONTestCase.hs b/test/JSONTestCase.hs new file mode 100644 index 000000000..c84a6aff7 --- /dev/null +++ b/test/JSONTestCase.hs @@ -0,0 +1,31 @@ +{-# LANGUAGE DeriveAnyClass #-} +module JSONTestCase where + +import Data.Map.Strict as Map +import Prelude +import Prologue +import Data.Aeson + +data JSONMetaRepo = JSONMetaRepo { repoPath :: !String + , repoUrl :: !String + , language :: !String + , syntaxes :: ![JSONMetaSyntax] + } deriving (Show, Generic, FromJSON) + +data JSONMetaSyntax = JSONMetaSyntax { syntax :: !String + , repoFilePath :: !String + , testCaseFilePath :: !String + , insert :: !String + , replacement :: !String + } deriving (Show, Generic, FromJSON) + +data JSONTestCase = JSONTestCase { gitDir :: !String + , testCaseDescription :: !String + , filePaths :: ![String] + , sha1 :: !String + , sha2 :: !String + , expectedResult :: !(Map Text (Map Text [Value])) + } deriving (Show, Generic, FromJSON) + +instance ToJSON JSONTestCase where + toEncoding = genericToEncoding defaultOptions diff --git a/test/SemanticGitDiffSpec.hs b/test/SemanticGitDiffSpec.hs new file mode 100644 index 000000000..1d9bcc462 --- /dev/null +++ b/test/SemanticGitDiffSpec.hs @@ -0,0 +1,53 @@ +module SemanticGitDiffSpec where + +import Arguments +import Data.Aeson +import Data.Map.Strict as Map +import Control.Exception +import qualified Data.ByteString.Lazy as DL +import JSONTestCase +import Test.Hspec (Spec, describe, it, SpecWith, runIO, parallel) +import Prelude +import Prologue +import Renderer +import SemanticDiff +import System.FilePath.Glob +import Data.Maybe (fromJust) +import Test.Hspec.Expectations.Pretty + +catchException :: IO [Text] -> IO [Text] +catchException = handle errorHandler + where errorHandler :: (SomeException -> IO [Text]) + errorHandler exception = return [toS . encode $ ["Crashed: " <> Prologue.show exception :: Text]] + +assertDiffSummary :: JSONTestCase -> Format -> (Either String (Map Text (Map Text [Value])) -> Either String (Map Text (Map Text [Value])) -> Expectation) -> Expectation +assertDiffSummary JSONTestCase {..} format matcher = do + diffs <- fetchDiffs $ args gitDir sha1 sha2 filePaths format + result <- catchException . pure . pure . concatOutputs $ diffs + let actual = eitherDecode . DL.fromStrict . encodeUtf8 . fromJust $ listToMaybe result + matcher actual (Right expectedResult) + +runTestsIn :: [FilePath] -> Format -> (Either String (Map Text (Map Text [Value])) -> Either String (Map Text (Map Text [Value])) -> Expectation) -> SpecWith () +runTestsIn filePaths format matcher = do + contents <- runIO $ traverse DL.readFile filePaths + let filePathContents = zip filePaths contents + let jsonContents = (\(filePath, content) -> (filePath, eitherDecode content)) <$> filePathContents :: [(FilePath, Either String [JSONTestCase])] + traverse_ handleJSONTestCase jsonContents + where handleJSONTestCase :: (FilePath, Either String [JSONTestCase]) -> SpecWith () + handleJSONTestCase (filePath, eitherJSONTestCase) = + case eitherJSONTestCase of + Left err -> it ("An error occurred " <> err <> " (" <> filePath <> ")") $ True `shouldBe` False + Right testCases -> traverse_ (\testCase -> it (testCaseDescription testCase) $ assertDiffSummary testCase format matcher) testCases + +spec :: Spec +spec = parallel $ do + diffSummaryFiles <- runIO $ testCaseFiles "test/corpus/diff-summaries" + diffSummaryToDoFiles <- runIO $ testCaseFiles "test/corpus/diff-summaries-todo" + diffSummaryCrasherFiles <- runIO $ testCaseFiles "test/corpus/diff-summary-crashers" + + describe "diff summaries" $ runTestsIn diffSummaryFiles Summary shouldBe + describe "diff summaries todo" $ runTestsIn diffSummaryToDoFiles Summary shouldNotBe + describe "diff summaries crashers todo" $ runTestsIn diffSummaryCrasherFiles Summary shouldBe + + where testCaseFiles :: String -> IO [FilePath] + testCaseFiles = globDir1 (compile "*/*.json") diff --git a/test/SpecIntegration.hs b/test/SpecIntegration.hs new file mode 100644 index 000000000..c4c8f09f8 --- /dev/null +++ b/test/SpecIntegration.hs @@ -0,0 +1,9 @@ +module Main where + +import Prologue +import qualified SemanticGitDiffSpec +import Test.Hspec + +main :: IO () +main = hspec $ parallel $ do + describe "DiffSummaries" SemanticGitDiffSpec.spec diff --git a/test/corpus/diff-summaries-crashers/javascript/.gitkeep b/test/corpus/diff-summaries-crashers/javascript/.gitkeep new file mode 100644 index 000000000..e69de29bb diff --git a/test/corpus/diff-summaries-todo/javascript/.gitkeep b/test/corpus/diff-summaries-todo/javascript/.gitkeep new file mode 100644 index 000000000..e69de29bb diff --git a/test/corpus/diff-summaries-todo/javascript/boolean-operator.json b/test/corpus/diff-summaries-todo/javascript/boolean-operator.json new file mode 100644 index 000000000..602c44b3b --- /dev/null +++ b/test/corpus/diff-summaries-todo/javascript/boolean-operator.json @@ -0,0 +1,30 @@ +[{ + "testCaseDescription": "javascript-boolean-operator-delete-insert-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ "Added the 'i || j' binary operator", "Deleted the 'i && j' binary operator" ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "c57d91166c3246b8e352252024dc21de6a42f707", + "gitDir": "test/corpus/repos/javascript", + "sha2": "244097ce5a74d6275f249d5159a6a14696a1eddf" +} +,{ + "testCaseDescription": "javascript-boolean-operator-replacement-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ "Added the 'i && j' binary operator", "Deleted the 'i || j' binary operator" ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "244097ce5a74d6275f249d5159a6a14696a1eddf", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0abfc815d9c5912259cfc25becb398a8f1444d40" +}] diff --git a/test/corpus/diff-summaries-todo/javascript/relational-operator.json b/test/corpus/diff-summaries-todo/javascript/relational-operator.json new file mode 100644 index 000000000..9c30b3b98 --- /dev/null +++ b/test/corpus/diff-summaries-todo/javascript/relational-operator.json @@ -0,0 +1,30 @@ +[{ + "testCaseDescription": "javascript-relational-operator-delete-insert-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ "Added the 'x < y' relational operator","Deleted the 'x <= y' relational operator" ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "f79a619c0277b82bb45cb1510847b78ba44ea31b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1fc7441b1fb64b171cf7892e3ce25bc55e25d754" +} +,{ + "testCaseDescription": "javascript-relational-operator-replacement-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ "Added the 'x <= y' relational operator","Deleted the 'x < y' relational operator" ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "1fc7441b1fb64b171cf7892e3ce25bc55e25d754", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e1d768da1e35b8066276dc5b5f9653442345948d" +}] diff --git a/test/corpus/diff-summaries/javascript/anonymous-function.json b/test/corpus/diff-summaries/javascript/anonymous-function.json new file mode 100644 index 000000000..300e1601a --- /dev/null +++ b/test/corpus/diff-summaries/javascript/anonymous-function.json @@ -0,0 +1,488 @@ +[{ + "testCaseDescription": "javascript-anonymous-function-insert-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added an anonymous(a, b) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "4e616c4976a8cc24c20fda3c6bfcde4cfa22483f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "11adb5f79753721a4cb9dd4c953f9baa21da78e4" +} +,{ + "testCaseDescription": "javascript-anonymous-function-replacement-insert-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added an anonymous(b, c) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added an anonymous(a, b) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "11adb5f79753721a4cb9dd4c953f9baa21da78e4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "22aa5c90ae1f387ad7f6fd2169bb97f5d3c57446" +} +,{ + "testCaseDescription": "javascript-anonymous-function-delete-insert-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 12 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 13 + ] + }, + { + "start": [ + 1, + 12 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 13 + ] + } + ] + }, + "summary": "Replaced the 'c' identifier with the 'b' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 24 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 24 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 28 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 29 + ] + }, + { + "start": [ + 1, + 28 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 29 + ] + } + ] + }, + "summary": "Replaced the 'c' identifier with the 'b' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "22aa5c90ae1f387ad7f6fd2169bb97f5d3c57446", + "gitDir": "test/corpus/repos/javascript", + "sha2": "00641b36f04df3262046fb678d56334975197898" +} +,{ + "testCaseDescription": "javascript-anonymous-function-replacement-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 12 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 13 + ] + }, + { + "start": [ + 1, + 12 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 13 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'c' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 24 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 24 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 28 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 29 + ] + }, + { + "start": [ + 1, + 28 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 29 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'c' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "00641b36f04df3262046fb678d56334975197898", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5005a8366ec0cd60cb0d36c5b8e70573ab05b5e2" +} +,{ + "testCaseDescription": "javascript-anonymous-function-delete-replacement-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted an anonymous(b, c) function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Deleted an anonymous(a, b) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added an anonymous(b, c) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "5005a8366ec0cd60cb0d36c5b8e70573ab05b5e2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1356b34dcce5152406f29f015d8342982a3704e4" +} +,{ + "testCaseDescription": "javascript-anonymous-function-delete-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted an anonymous(a, b) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "1356b34dcce5152406f29f015d8342982a3704e4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "22d5b6e950763c553f1efb105400c69ab6f34b31" +} +,{ + "testCaseDescription": "javascript-anonymous-function-delete-rest-test", + "expectedResult": { + "changes": { + "anonymous-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-function.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted an anonymous(b, c) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-function.js" + ], + "sha1": "22d5b6e950763c553f1efb105400c69ab6f34b31", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d03e64156e1eccacaee03b2180ecdeba6ca0385c" +}] diff --git a/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json new file mode 100644 index 000000000..2f4388594 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-anonymous-parameterless-function-insert-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 28 + ] + } + }, + "summary": "Added an anonymous() function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "d03e64156e1eccacaee03b2180ecdeba6ca0385c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "74ca1b76b63e514abaf450801b7c266a075d88cf" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Added an anonymous() function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 2, + 28 + ] + } + }, + "summary": "Added an anonymous() function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "74ca1b76b63e514abaf450801b7c266a075d88cf", + "gitDir": "test/corpus/repos/javascript", + "sha2": "dbe1defa8484a6fe83354587d0c2d694d53d85d7" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 21 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 28 + ] + }, + { + "start": [ + 1, + 21 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'hello' string with the 'hi' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "dbe1defa8484a6fe83354587d0c2d694d53d85d7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ebe1b4c63b69969ba5879d11d968a450a4764320" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 21 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 21 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 28 + ] + } + ] + }, + "summary": "Replaced the 'hi' string with the 'hello' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "ebe1b4c63b69969ba5879d11d968a450a4764320", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2f5c02d12967641470fcd29a06d32300cecc578b" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted an anonymous() function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 2, + 28 + ] + } + }, + "summary": "Deleted an anonymous() function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 2, + 31 + ] + } + }, + "summary": "Added an anonymous() function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "2f5c02d12967641470fcd29a06d32300cecc578b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "07dbb53e127cb5de0e07c6f449d2959038088696" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-delete-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 28 + ] + } + }, + "summary": "Deleted an anonymous() function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "07dbb53e127cb5de0e07c6f449d2959038088696", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4d244392442a153a1495219111c1fa2929fae4ac" +} +,{ + "testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test", + "expectedResult": { + "changes": { + "anonymous-parameterless-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "anonymous-parameterless-function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted an anonymous() function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "anonymous-parameterless-function.js" + ], + "sha1": "4d244392442a153a1495219111c1fa2929fae4ac", + "gitDir": "test/corpus/repos/javascript", + "sha2": "59872fcdcee9cd22104933bbc925d9987cd393b6" +}] diff --git a/test/corpus/diff-summaries/javascript/array.json b/test/corpus/diff-summaries/javascript/array.json new file mode 100644 index 000000000..2dcd6534c --- /dev/null +++ b/test/corpus/diff-summaries/javascript/array.json @@ -0,0 +1,282 @@ +[{ + "testCaseDescription": "javascript-array-insert-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "array.js", + "end": [ + 1, + 12 + ] + } + }, + "summary": "Added the '[ \"item1\" ]' array", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "72a672d52b6952c146edab2927b3b05abd022921", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8a68989a0d6ab0cd555a73289acaf3ee5100c31d" +} +,{ + "testCaseDescription": "javascript-array-replacement-insert-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "array.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Added the '[ \"item1\", \"item2\" ]' array", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "array.js", + "end": [ + 2, + 12 + ] + } + }, + "summary": "Added the '[ \"item1\" ]' array", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "8a68989a0d6ab0cd555a73289acaf3ee5100c31d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "aba697e2f9d98d3f14f31cfe741d1c0150c3a99a" +} +,{ + "testCaseDescription": "javascript-array-delete-insert-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "this": { + "start": [ + 1, + 12 + ], + "name": "array.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Deleted the \"item2\" string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "aba697e2f9d98d3f14f31cfe741d1c0150c3a99a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7616278362cc2f6254d943d75632c5235bba9971" +} +,{ + "testCaseDescription": "javascript-array-replacement-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "that": { + "start": [ + 1, + 12 + ], + "name": "array.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Added the \"item2\" string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "7616278362cc2f6254d943d75632c5235bba9971", + "gitDir": "test/corpus/repos/javascript", + "sha2": "44749342699a37f8ef292b98a3982097a3d08011" +} +,{ + "testCaseDescription": "javascript-array-delete-replacement-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "array.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the '[ \"item1\", \"item2\" ]' array", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "array.js", + "end": [ + 2, + 12 + ] + } + }, + "summary": "Deleted the '[ \"item1\" ]' array", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "array.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Added the '[ \"item1\", \"item2\" ]' array", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "44749342699a37f8ef292b98a3982097a3d08011", + "gitDir": "test/corpus/repos/javascript", + "sha2": "fe6708bd26fdab5406160bac05f1cff56de363f9" +} +,{ + "testCaseDescription": "javascript-array-delete-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "array.js", + "end": [ + 1, + 12 + ] + } + }, + "summary": "Deleted the '[ \"item1\" ]' array", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "fe6708bd26fdab5406160bac05f1cff56de363f9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1e7aa51504a3eb084aaca63663658690ce3f65f0" +} +,{ + "testCaseDescription": "javascript-array-delete-rest-test", + "expectedResult": { + "changes": { + "array.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "array.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the '[ \"item1\", \"item2\" ]' array", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "array.js" + ], + "sha1": "1e7aa51504a3eb084aaca63663658690ce3f65f0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "492ece78ac243f74d0f0bfce83c94b7162c1eaa6" +}] diff --git a/test/corpus/diff-summaries/javascript/arrow-function.json b/test/corpus/diff-summaries/javascript/arrow-function.json new file mode 100644 index 000000000..4d6192573 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/arrow-function.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-arrow-function-insert-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "arrow-function.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Added an anonymous(f, g) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "142158e6e72a9a884b0d89c0b044b5c1473248db", + "gitDir": "test/corpus/repos/javascript", + "sha2": "13ec03f9e751e39a9264ab096a2340c206e46e94" +} +,{ + "testCaseDescription": "javascript-arrow-function-replacement-insert-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "arrow-function.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Added an anonymous(f, g) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "arrow-function.js", + "end": [ + 2, + 24 + ] + } + }, + "summary": "Added an anonymous(f, g) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "13ec03f9e751e39a9264ab096a2340c206e46e94", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5bed5bece02a8f7e16801c1e44d6b73af832e316" +} +,{ + "testCaseDescription": "javascript-arrow-function-delete-insert-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "arrow-function.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "arrow-function.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'g' identifier with the 'h' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "5bed5bece02a8f7e16801c1e44d6b73af832e316", + "gitDir": "test/corpus/repos/javascript", + "sha2": "93d231ad655a0f193a27b6aed6e5daee14efb962" +} +,{ + "testCaseDescription": "javascript-arrow-function-replacement-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "arrow-function.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "arrow-function.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'h' identifier with the 'g' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "93d231ad655a0f193a27b6aed6e5daee14efb962", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bdf1809e96da6408d7fe4992cf0cb8b2617c283b" +} +,{ + "testCaseDescription": "javascript-arrow-function-delete-replacement-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "arrow-function.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Deleted an anonymous(f, g) function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "arrow-function.js", + "end": [ + 2, + 24 + ] + } + }, + "summary": "Deleted an anonymous(f, g) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "arrow-function.js", + "end": [ + 2, + 24 + ] + } + }, + "summary": "Added an anonymous(f, g) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "bdf1809e96da6408d7fe4992cf0cb8b2617c283b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "47663edfd71e7dca4832c0c6981e05116a2ed347" +} +,{ + "testCaseDescription": "javascript-arrow-function-delete-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "arrow-function.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Deleted an anonymous(f, g) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "47663edfd71e7dca4832c0c6981e05116a2ed347", + "gitDir": "test/corpus/repos/javascript", + "sha2": "89d1bae5033feb4a97fe91084db2a9b2faa48239" +} +,{ + "testCaseDescription": "javascript-arrow-function-delete-rest-test", + "expectedResult": { + "changes": { + "arrow-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "arrow-function.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Deleted an anonymous(f, g) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "arrow-function.js" + ], + "sha1": "89d1bae5033feb4a97fe91084db2a9b2faa48239", + "gitDir": "test/corpus/repos/javascript", + "sha2": "304e0c432994c642daa18c284f4c1578416e77e1" +}] diff --git a/test/corpus/diff-summaries/javascript/assignment.json b/test/corpus/diff-summaries/javascript/assignment.json new file mode 100644 index 000000000..871c9ab87 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/assignment.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-assignment-insert-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "e66aa2b6bacc2bbd796427540227b298518b1389", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3956fb4eec4f0bd0a62f4e0b55ccaf0125576854" +} +,{ + "testCaseDescription": "javascript-assignment-replacement-insert-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "assignment.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added the 'x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "3956fb4eec4f0bd0a62f4e0b55ccaf0125576854", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d1726bb6040b8c5f6358f7d1af2ebc11e7d96e9f" +} +,{ + "testCaseDescription": "javascript-assignment-delete-insert-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 5 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + }, + { + "start": [ + 1, + 5 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + ] + }, + "summary": "Replaced '1' with '0' in an assignment to x", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "d1726bb6040b8c5f6358f7d1af2ebc11e7d96e9f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "01f04fbd4037191df6536ca1d542eb8f2678082d" +} +,{ + "testCaseDescription": "javascript-assignment-replacement-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 5 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + }, + { + "start": [ + 1, + 5 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + ] + }, + "summary": "Replaced '0' with '1' in an assignment to x", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "01f04fbd4037191df6536ca1d542eb8f2678082d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "95e89035c2067fbcd267d77dfdd886961f91abeb" +} +,{ + "testCaseDescription": "javascript-assignment-delete-replacement-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "assignment.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Deleted the 'x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "assignment.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added the 'x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "95e89035c2067fbcd267d77dfdd886961f91abeb", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8faa9a17a52e98b1ad0f1162f486efdfda8f8e5c" +} +,{ + "testCaseDescription": "javascript-assignment-delete-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "8faa9a17a52e98b1ad0f1162f486efdfda8f8e5c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9032da30a2fccadbd1e19d8d0d0636948a92e1e3" +} +,{ + "testCaseDescription": "javascript-assignment-delete-rest-test", + "expectedResult": { + "changes": { + "assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "assignment.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "assignment.js" + ], + "sha1": "9032da30a2fccadbd1e19d8d0d0636948a92e1e3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "24ea895fcb8c904a8d057c536eb56be4a8928e33" +}] diff --git a/test/corpus/diff-summaries/javascript/bitwise-operator.json b/test/corpus/diff-summaries/javascript/bitwise-operator.json new file mode 100644 index 000000000..fed05f18a --- /dev/null +++ b/test/corpus/diff-summaries/javascript/bitwise-operator.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-bitwise-operator-insert-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'i >> j' bitwise operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "e50fb0bfd581bcee25d02606b04bc985c4e8c2d5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ea02f16ab7419b380ec808099788e04be860b436" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'i >> k' bitwise operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'i >> j' bitwise operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "ea02f16ab7419b380ec808099788e04be860b436", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f9001c917ef267da3f658296ca2acf5593d3782e" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-delete-insert-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'k' identifier with the 'j' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "f9001c917ef267da3f658296ca2acf5593d3782e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "580bdafd78d48683a535d1da85a0f9810e776bca" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-replacement-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'j' identifier with the 'k' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "580bdafd78d48683a535d1da85a0f9810e776bca", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3ca9b47b8791704f4d65314daf724c3ff3b77ad3" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i >> k' bitwise operator", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Deleted the 'i >> j' bitwise operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'i >> k' bitwise operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "3ca9b47b8791704f4d65314daf724c3ff3b77ad3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "74883181e363b757e7e66fa0e4fc525854b0ce1c" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-delete-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i >> j' bitwise operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "74883181e363b757e7e66fa0e4fc525854b0ce1c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3f724f4ce7be26db4a43de14aaefcec5c253c2f0" +} +,{ + "testCaseDescription": "javascript-bitwise-operator-delete-rest-test", + "expectedResult": { + "changes": { + "bitwise-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "bitwise-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i >> k' bitwise operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "bitwise-operator.js" + ], + "sha1": "3f724f4ce7be26db4a43de14aaefcec5c253c2f0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8cdb0cc77bfe88b76c86dcde66d08f97f11182f3" +}] diff --git a/test/corpus/diff-summaries/javascript/boolean-operator.json b/test/corpus/diff-summaries/javascript/boolean-operator.json new file mode 100644 index 000000000..340eddd16 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/boolean-operator.json @@ -0,0 +1,208 @@ +[{ + "testCaseDescription": "javascript-boolean-operator-insert-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'i || j' boolean operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "d7edfafd0028d88e036ad5af083bd4c0eaf821d5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c1fd7ccb58cd391d8a2cb427baf9451e6ef0734c" +} +,{ + "testCaseDescription": "javascript-boolean-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'i && j' boolean operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'i || j' boolean operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "c1fd7ccb58cd391d8a2cb427baf9451e6ef0734c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "029b382cce42f0b823e8f6c7fa383b3236d7f831" +} +,{ + "testCaseDescription": "javascript-boolean-operator-delete-insert-test", + "expectedResult": { + "changes": {}, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "029b382cce42f0b823e8f6c7fa383b3236d7f831", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8fef1ef2ddf9da13147ee48a19dd104f020b4f1d" +} +,{ + "testCaseDescription": "javascript-boolean-operator-replacement-test", + "expectedResult": { + "changes": {}, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "8fef1ef2ddf9da13147ee48a19dd104f020b4f1d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4f3d6544f9d7e379865cc08309dc7276695d864c" +} +,{ + "testCaseDescription": "javascript-boolean-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i && j' boolean operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "4f3d6544f9d7e379865cc08309dc7276695d864c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "15041bb73bf8501e01192e57cfdd6f1d889776e9" +} +,{ + "testCaseDescription": "javascript-boolean-operator-delete-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i || j' boolean operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "15041bb73bf8501e01192e57cfdd6f1d889776e9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d5a15780faa29b2762f02eba66a6d4c4e3510b8f" +} +,{ + "testCaseDescription": "javascript-boolean-operator-delete-rest-test", + "expectedResult": { + "changes": { + "boolean-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "boolean-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'i && j' boolean operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "boolean-operator.js" + ], + "sha1": "d5a15780faa29b2762f02eba66a6d4c4e3510b8f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e50fb0bfd581bcee25d02606b04bc985c4e8c2d5" +}] diff --git a/test/corpus/diff-summaries/javascript/chained-callbacks.json b/test/corpus/diff-summaries/javascript/chained-callbacks.json new file mode 100644 index 000000000..963756c61 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/chained-callbacks.json @@ -0,0 +1,428 @@ +[{ + "testCaseDescription": "javascript-chained-callbacks-insert-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Added the 'this.map(…)' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "3717d88f796c52203c37c0d8440b823c78192c49", + "gitDir": "test/corpus/repos/javascript", + "sha2": "72ab8f58d72d44c1059e734e3a396d97eb072f23" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-replacement-insert-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Added the 'this.reduce(…)' method call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 2, + 39 + ] + } + }, + "summary": "Added the 'this.map(…)' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "72ab8f58d72d44c1059e734e3a396d97eb072f23", + "gitDir": "test/corpus/repos/javascript", + "sha2": "57f2199dba16641866f45c7554c0bbb5b912dc36" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-delete-insert-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 12 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 9 + ] + } + ] + }, + "summary": "Replaced the 'reduce' identifier with the 'map' identifier in the this.map(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 35 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 36 + ] + }, + { + "start": [ + 1, + 32 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 33 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.map(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 37 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 38 + ] + }, + { + "start": [ + 1, + 34 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 35 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.map(…) method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "57f2199dba16641866f45c7554c0bbb5b912dc36", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d00c5e7da7eb6dfcdc63fa490b3e1f5c1481d41d" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-replacement-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 9 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 12 + ] + } + ] + }, + "summary": "Replaced the 'map' identifier with the 'reduce' identifier in the this.reduce(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 32 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 33 + ] + }, + { + "start": [ + 1, + 35 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 36 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier in the this.reduce(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 34 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 35 + ] + }, + { + "start": [ + 1, + 37 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 38 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier in the this.reduce(…) method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "d00c5e7da7eb6dfcdc63fa490b3e1f5c1481d41d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9c042fe39e2f19c0e5f6cd64026de2a03c4c0896" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-delete-replacement-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'this.reduce(…)' method call", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 2, + 39 + ] + } + }, + "summary": "Deleted the 'this.map(…)' method call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Added the 'this.reduce(…)' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "9c042fe39e2f19c0e5f6cd64026de2a03c4c0896", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6a9959f752a3845f39f9044f342173af99c4ee6f" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-delete-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Deleted the 'this.map(…)' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "6a9959f752a3845f39f9044f342173af99c4ee6f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a9b91380938e6d3842fd308280c0a638bb537ba5" +} +,{ + "testCaseDescription": "javascript-chained-callbacks-delete-rest-test", + "expectedResult": { + "changes": { + "chained-callbacks.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-callbacks.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'this.reduce(…)' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-callbacks.js" + ], + "sha1": "a9b91380938e6d3842fd308280c0a638bb537ba5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cf31ddf834d011d1d55eee3da85c70f15eea67f1" +}] diff --git a/test/corpus/diff-summaries/javascript/chained-property-access.json b/test/corpus/diff-summaries/javascript/chained-property-access.json new file mode 100644 index 000000000..9622ff7c4 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/chained-property-access.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-chained-property-access-insert-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 2, + 1 + ] + } + }, + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "07c5dd47cd837cd06d7d034c049ea6002a5e0980", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1c568a6a258b36c95bb3701e878ae08a1c9e79ba" +} +,{ + "testCaseDescription": "javascript-chained-property-access-replacement-insert-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 2, + 1 + ] + } + }, + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 3, + 1 + ] + } + }, + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "1c568a6a258b36c95bb3701e878ae08a1c9e79ba", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7abc5ff0a2ca47dde4b277648bc657d825c910d3" +} +,{ + "testCaseDescription": "javascript-chained-property-access-delete-insert-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 33 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 43 + ] + }, + { + "start": [ + 1, + 33 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 41 + ] + } + ] + }, + "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 60 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 70 + ] + }, + { + "start": [ + 1, + 58 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 66 + ] + } + ] + }, + "summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…).fail(…) method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "7abc5ff0a2ca47dde4b277648bc657d825c910d3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6b0bfd2f77ff616e1f944328fbcac86513799b91" +} +,{ + "testCaseDescription": "javascript-chained-property-access-replacement-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 33 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 41 + ] + }, + { + "start": [ + 1, + 33 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 43 + ] + } + ] + }, + "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 58 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 66 + ] + }, + { + "start": [ + 1, + 60 + ], + "name": "chained-property-access.js", + "end": [ + 1, + 70 + ] + } + ] + }, + "summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…).fail(…) method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "6b0bfd2f77ff616e1f944328fbcac86513799b91", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f87e928b3a52d1d9457b8389cc414276799c70c6" +} +,{ + "testCaseDescription": "javascript-chained-property-access-delete-replacement-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 2, + 1 + ] + } + }, + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 3, + 1 + ] + } + }, + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 3, + 1 + ] + } + }, + "summary": "Added the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "f87e928b3a52d1d9457b8389cc414276799c70c6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1056591b7f8f24ed7718a8d9b3f515eb0b48a29a" +} +,{ + "testCaseDescription": "javascript-chained-property-access-delete-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 2, + 1 + ] + } + }, + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "1056591b7f8f24ed7718a8d9b3f515eb0b48a29a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "de450f4e2eb24b89b5d66301b772d4f9714e7919" +} +,{ + "testCaseDescription": "javascript-chained-property-access-delete-rest-test", + "expectedResult": { + "changes": { + "chained-property-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "chained-property-access.js", + "end": [ + 2, + 1 + ] + } + }, + "summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "chained-property-access.js" + ], + "sha1": "de450f4e2eb24b89b5d66301b772d4f9714e7919", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3717d88f796c52203c37c0d8440b823c78192c49" +}] diff --git a/test/corpus/diff-summaries/javascript/class.json b/test/corpus/diff-summaries/javascript/class.json new file mode 100644 index 000000000..f15fe99a2 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/class.json @@ -0,0 +1,428 @@ +[{ + "testCaseDescription": "javascript-class-insert-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "class.js", + "end": [ + 1, + 87 + ] + } + }, + "summary": "Added the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "05ac6c8e85dcf3c89620fde92c3f7cccf4ca5d18", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d0516334378ca54458689813316ca9f3e792b9d0" +} +,{ + "testCaseDescription": "javascript-class-replacement-insert-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "class.js", + "end": [ + 1, + 85 + ] + } + }, + "summary": "Added the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "class.js", + "end": [ + 2, + 87 + ] + } + }, + "summary": "Added the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "d0516334378ca54458689813316ca9f3e792b9d0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f0d1b629278eb502b25fd9d266065451cdd48405" +} +,{ + "testCaseDescription": "javascript-class-delete-insert-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "class.js", + "end": [ + 1, + 23 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "class.js", + "end": [ + 1, + 23 + ] + } + ] + }, + "summary": "Replaced the 'foo' identifier with the 'one' identifier in the one method of the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 42 + ], + "name": "class.js", + "end": [ + 1, + 45 + ] + }, + { + "start": [ + 1, + 42 + ], + "name": "class.js", + "end": [ + 1, + 45 + ] + } + ] + }, + "summary": "Replaced the 'bar' identifier with the 'two' identifier in the two method of the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 63 + ], + "name": "class.js", + "end": [ + 1, + 66 + ] + }, + { + "start": [ + 1, + 63 + ], + "name": "class.js", + "end": [ + 1, + 68 + ] + } + ] + }, + "summary": "Replaced the 'baz' identifier with the 'three' identifier in the three method of the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "f0d1b629278eb502b25fd9d266065451cdd48405", + "gitDir": "test/corpus/repos/javascript", + "sha2": "287224754bbb2fc1d5d3e66af924ab2e4b1a6e15" +} +,{ + "testCaseDescription": "javascript-class-replacement-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "class.js", + "end": [ + 1, + 23 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "class.js", + "end": [ + 1, + 23 + ] + } + ] + }, + "summary": "Replaced the 'one' identifier with the 'foo' identifier in the foo method of the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 42 + ], + "name": "class.js", + "end": [ + 1, + 45 + ] + }, + { + "start": [ + 1, + 42 + ], + "name": "class.js", + "end": [ + 1, + 45 + ] + } + ] + }, + "summary": "Replaced the 'two' identifier with the 'bar' identifier in the bar method of the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 63 + ], + "name": "class.js", + "end": [ + 1, + 68 + ] + }, + { + "start": [ + 1, + 63 + ], + "name": "class.js", + "end": [ + 1, + 66 + ] + } + ] + }, + "summary": "Replaced the 'three' identifier with the 'baz' identifier in the baz method of the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "287224754bbb2fc1d5d3e66af924ab2e4b1a6e15", + "gitDir": "test/corpus/repos/javascript", + "sha2": "faf44add1dac5da1190877cfbe29f2166a87cb70" +} +,{ + "testCaseDescription": "javascript-class-delete-replacement-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "class.js", + "end": [ + 1, + 85 + ] + } + }, + "summary": "Deleted the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "class.js", + "end": [ + 2, + 87 + ] + } + }, + "summary": "Deleted the 'Foo' class", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "class.js", + "end": [ + 2, + 85 + ] + } + }, + "summary": "Added the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "faf44add1dac5da1190877cfbe29f2166a87cb70", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c9d86ff39cf88d63bef375c0f1f6bee48fad7469" +} +,{ + "testCaseDescription": "javascript-class-delete-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "class.js", + "end": [ + 1, + 87 + ] + } + }, + "summary": "Deleted the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "c9d86ff39cf88d63bef375c0f1f6bee48fad7469", + "gitDir": "test/corpus/repos/javascript", + "sha2": "925c03b275a76023914adc08c757bb7375f31bbd" +} +,{ + "testCaseDescription": "javascript-class-delete-rest-test", + "expectedResult": { + "changes": { + "class.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "class.js", + "end": [ + 1, + 85 + ] + } + }, + "summary": "Deleted the 'Foo' class", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "class.js" + ], + "sha1": "925c03b275a76023914adc08c757bb7375f31bbd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "72a672d52b6952c146edab2927b3b05abd022921" +}] diff --git a/test/corpus/diff-summaries/javascript/comma-operator.json b/test/corpus/diff-summaries/javascript/comma-operator.json new file mode 100644 index 000000000..b1fc0babb --- /dev/null +++ b/test/corpus/diff-summaries/javascript/comma-operator.json @@ -0,0 +1,418 @@ +[{ + "testCaseDescription": "javascript-comma-operator-insert-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 8 + ], + "name": "comma-operator.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'b' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "ea966e7428b15b541246b765517db3f0ef1c6af8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "89fefd3a2c9fb540528c4000768a6ef747cd59d0" +} +,{ + "testCaseDescription": "javascript-comma-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Added the 'c' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "comma-operator.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 8 + ], + "name": "comma-operator.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Added the 'b' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "89fefd3a2c9fb540528c4000768a6ef747cd59d0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d18b8317fdd54ea56ecc8a6f5163100fbb90804f" +} +,{ + "testCaseDescription": "javascript-comma-operator-delete-insert-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 8 + ], + "name": "comma-operator.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'b' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Deleted the 'c' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "d18b8317fdd54ea56ecc8a6f5163100fbb90804f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "004af9fd96c38181e344af8dab95b192f1c1dfe2" +} +,{ + "testCaseDescription": "javascript-comma-operator-replacement-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Added the 'c' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "comma-operator.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'b' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "004af9fd96c38181e344af8dab95b192f1c1dfe2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0d2764a507da37777c1f1726fba8261b84f7bcb0" +} +,{ + "testCaseDescription": "javascript-comma-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Deleted the 'c' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "comma-operator.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Deleted the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 8 + ], + "name": "comma-operator.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Deleted the 'b' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "comma-operator.js", + "end": [ + 2, + 23 + ] + } + }, + "summary": "Added the 'c' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "0d2764a507da37777c1f1726fba8261b84f7bcb0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7ce2f66bf4aa19bb752574fed5e2416e405dd67f" +} +,{ + "testCaseDescription": "javascript-comma-operator-delete-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'a' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "comma-operator.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'b' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "7ce2f66bf4aa19bb752574fed5e2416e405dd67f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2e0718a5d9166e53a839ce51dccca62297668a6d" +} +,{ + "testCaseDescription": "javascript-comma-operator-delete-rest-test", + "expectedResult": { + "changes": { + "comma-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comma-operator.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Deleted the 'c' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comma-operator.js" + ], + "sha1": "2e0718a5d9166e53a839ce51dccca62297668a6d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7d593b800284097a4d4f70fe25aebef1cbbe69c3" +}] diff --git a/test/corpus/diff-summaries/javascript/comment.json b/test/corpus/diff-summaries/javascript/comment.json new file mode 100644 index 000000000..86321da62 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/comment.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-comment-insert-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 1, + 22 + ] + } + }, + "summary": "Added the '// This is a property' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "b00fa825ca435ba80830373e95ab22dd77ce9326", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2e607c097d74497502eb9b05f61574413df5a704" +} +,{ + "testCaseDescription": "javascript-comment-replacement-insert-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 3, + 3 + ] + } + }, + "summary": "Added the '/*\n * This is a method\n*/' comment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 4, + 1 + ], + "name": "comment.js", + "end": [ + 4, + 22 + ] + } + }, + "summary": "Added the '// This is a property' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "2e607c097d74497502eb9b05f61574413df5a704", + "gitDir": "test/corpus/repos/javascript", + "sha2": "03b1da21726c00724121764c61d9148a5561e972" +} +,{ + "testCaseDescription": "javascript-comment-delete-insert-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 3, + 3 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 1, + 22 + ] + } + ] + }, + "summary": "Replaced the '/*\n * This is a method\n*/' comment with the '// This is a property' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "03b1da21726c00724121764c61d9148a5561e972", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2bfa931c9fdb2a9e6a5362bc4edcf55fd54afc5b" +} +,{ + "testCaseDescription": "javascript-comment-replacement-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 1, + 22 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 3, + 3 + ] + } + ] + }, + "summary": "Replaced the '// This is a property' comment with the '/*\n * This is a method\n*/' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "2bfa931c9fdb2a9e6a5362bc4edcf55fd54afc5b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "16abf9f672b794a292a6328925ecb9e5b77e4e3e" +} +,{ + "testCaseDescription": "javascript-comment-delete-replacement-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 3, + 3 + ] + } + }, + "summary": "Deleted the '/*\n * This is a method\n*/' comment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 4, + 1 + ], + "name": "comment.js", + "end": [ + 4, + 22 + ] + } + }, + "summary": "Deleted the '// This is a property' comment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "comment.js", + "end": [ + 4, + 3 + ] + } + }, + "summary": "Added the '/*\n * This is a method\n*/' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "16abf9f672b794a292a6328925ecb9e5b77e4e3e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "253e6af1000fd09a2472ce58f2294e56a5b072a5" +} +,{ + "testCaseDescription": "javascript-comment-delete-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 1, + 22 + ] + } + }, + "summary": "Deleted the '// This is a property' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "253e6af1000fd09a2472ce58f2294e56a5b072a5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5dd2f4591f46cc567e9ef4d08528a8139f329bfe" +} +,{ + "testCaseDescription": "javascript-comment-delete-rest-test", + "expectedResult": { + "changes": { + "comment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "comment.js", + "end": [ + 3, + 3 + ] + } + }, + "summary": "Deleted the '/*\n * This is a method\n*/' comment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "comment.js" + ], + "sha1": "5dd2f4591f46cc567e9ef4d08528a8139f329bfe", + "gitDir": "test/corpus/repos/javascript", + "sha2": "df276ed5f435d4cf1363008ae573ea99ba39e175" +}] diff --git a/test/corpus/diff-summaries/javascript/constructor-call.json b/test/corpus/diff-summaries/javascript/constructor-call.json new file mode 100644 index 000000000..12e5f9518 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/constructor-call.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-constructor-call-insert-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "constructor-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Added the 'module.Klass(1, \"two\")' constructor", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "e5315f0371489f42d527c318faa1406833bb3c86", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3ab58f25a58c73e8b63bf047879dc80453f67ca3" +} +,{ + "testCaseDescription": "javascript-constructor-call-replacement-insert-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "constructor-call.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Added the 'module.Klass(1, \"three\")' constructor", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "constructor-call.js", + "end": [ + 2, + 27 + ] + } + }, + "summary": "Added the 'module.Klass(1, \"two\")' constructor", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "3ab58f25a58c73e8b63bf047879dc80453f67ca3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1481a195f0a198d73a647c8b75da4d7dc7221894" +} +,{ + "testCaseDescription": "javascript-constructor-call-delete-insert-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 21 + ], + "name": "constructor-call.js", + "end": [ + 1, + 28 + ] + }, + { + "start": [ + 1, + 21 + ], + "name": "constructor-call.js", + "end": [ + 1, + 26 + ] + } + ] + }, + "summary": "Replaced the \"three\" string with the \"two\" string in the module.Klass(1, \"two\") method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "1481a195f0a198d73a647c8b75da4d7dc7221894", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ba525ceaac882771bf3028d5c750f938114e96d2" +} +,{ + "testCaseDescription": "javascript-constructor-call-replacement-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 21 + ], + "name": "constructor-call.js", + "end": [ + 1, + 26 + ] + }, + { + "start": [ + 1, + 21 + ], + "name": "constructor-call.js", + "end": [ + 1, + 28 + ] + } + ] + }, + "summary": "Replaced the \"two\" string with the \"three\" string in the module.Klass(1, \"three\") method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "ba525ceaac882771bf3028d5c750f938114e96d2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4b4ec51a435eea48627eedf5abc5e418a1fe6a55" +} +,{ + "testCaseDescription": "javascript-constructor-call-delete-replacement-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "constructor-call.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'module.Klass(1, \"three\")' constructor", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "constructor-call.js", + "end": [ + 2, + 27 + ] + } + }, + "summary": "Deleted the 'module.Klass(1, \"two\")' constructor", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "constructor-call.js", + "end": [ + 2, + 29 + ] + } + }, + "summary": "Added the 'module.Klass(1, \"three\")' constructor", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "4b4ec51a435eea48627eedf5abc5e418a1fe6a55", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5d2a91a3bae082f9b7805f6dfca606e93e795432" +} +,{ + "testCaseDescription": "javascript-constructor-call-delete-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "constructor-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Deleted the 'module.Klass(1, \"two\")' constructor", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "5d2a91a3bae082f9b7805f6dfca606e93e795432", + "gitDir": "test/corpus/repos/javascript", + "sha2": "dbb99c0fe06226687ed383f68ef1b5d4e15f35f6" +} +,{ + "testCaseDescription": "javascript-constructor-call-delete-rest-test", + "expectedResult": { + "changes": { + "constructor-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "constructor-call.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'module.Klass(1, \"three\")' constructor", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "constructor-call.js" + ], + "sha1": "dbb99c0fe06226687ed383f68ef1b5d4e15f35f6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a871e92442fa237af75a13a311d49a15bcea9444" +}] diff --git a/test/corpus/diff-summaries/javascript/delete-operator.json b/test/corpus/diff-summaries/javascript/delete-operator.json new file mode 100644 index 000000000..8f619991d --- /dev/null +++ b/test/corpus/diff-summaries/javascript/delete-operator.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-delete-operator-insert-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Added the 'delete thing['prop']' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "0014c5d8fc3e6f9d08e268ebbb2d42919d5b4991", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1bf82468139fc9bae884877d4642cb378d30e388" +} +,{ + "testCaseDescription": "javascript-delete-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Added the 'delete thing.prop' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "delete-operator.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Added the 'delete thing['prop']' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "1bf82468139fc9bae884877d4642cb378d30e388", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8daf29e348abe84e12f3876f0d414a3d1ff66133" +} +,{ + "testCaseDescription": "javascript-delete-operator-delete-insert-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 18 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'delete thing.prop' operator with the 'delete thing['prop']' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "8daf29e348abe84e12f3876f0d414a3d1ff66133", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c0a5da4ddc67f830084586b2327558655a70855a" +} +,{ + "testCaseDescription": "javascript-delete-operator-replacement-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 18 + ] + } + ] + }, + "summary": "Replaced the 'delete thing['prop']' operator with the 'delete thing.prop' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "c0a5da4ddc67f830084586b2327558655a70855a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cec4caaf5abbc34a89ed4f4695648f6c07a47419" +} +,{ + "testCaseDescription": "javascript-delete-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'delete thing.prop' operator", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "delete-operator.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Deleted the 'delete thing['prop']' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "delete-operator.js", + "end": [ + 2, + 18 + ] + } + }, + "summary": "Added the 'delete thing.prop' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "cec4caaf5abbc34a89ed4f4695648f6c07a47419", + "gitDir": "test/corpus/repos/javascript", + "sha2": "497cf34db38a72640cc8ce570306c591bba9f02f" +} +,{ + "testCaseDescription": "javascript-delete-operator-delete-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the 'delete thing['prop']' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "497cf34db38a72640cc8ce570306c591bba9f02f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "045574a46a7e7f97875d188458465b12f0c742a8" +} +,{ + "testCaseDescription": "javascript-delete-operator-delete-rest-test", + "expectedResult": { + "changes": { + "delete-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "delete-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'delete thing.prop' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "delete-operator.js" + ], + "sha1": "045574a46a7e7f97875d188458465b12f0c742a8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "91bb86f2c473fce6ff1ddd4c4e25a6362131920f" +}] diff --git a/test/corpus/diff-summaries/javascript/do-while-statement.json b/test/corpus/diff-summaries/javascript/do-while-statement.json new file mode 100644 index 000000000..4a0b7f166 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/do-while-statement.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-do-while-statement-insert-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Added the 'true' do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "a373c4a7201be2aa145e60cf15e0adfedc85aac5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cebe84530c2734410e83fadc8f0aeb3a6b3ce715" +} +,{ + "testCaseDescription": "javascript-do-while-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Added the 'false' do/while statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Added the 'true' do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "cebe84530c2734410e83fadc8f0aeb3a6b3ce715", + "gitDir": "test/corpus/repos/javascript", + "sha2": "87bbd6f72fcd3eef6b92d656dc2fe4fb9139ba94" +} +,{ + "testCaseDescription": "javascript-do-while-statement-delete-insert-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 18 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 29 + ] + }, + { + "start": [ + 1, + 18 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 24 + ] + } + ] + }, + "summary": "Replaced the 'replacement' identifier with the 'insert' identifier in the console.log(insert) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 41 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 46 + ] + }, + { + "start": [ + 1, + 36 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 40 + ] + } + ] + }, + "summary": "Replaced 'false' with 'true' in the true do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "87bbd6f72fcd3eef6b92d656dc2fe4fb9139ba94", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d9f0f483d83873729799b3d7daccf467ff355a13" +} +,{ + "testCaseDescription": "javascript-do-while-statement-replacement-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 18 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 24 + ] + }, + { + "start": [ + 1, + 18 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 29 + ] + } + ] + }, + "summary": "Replaced the 'insert' identifier with the 'replacement' identifier in the console.log(replacement) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 36 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 40 + ] + }, + { + "start": [ + 1, + 41 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 46 + ] + } + ] + }, + "summary": "Replaced 'true' with 'false' in the false do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "d9f0f483d83873729799b3d7daccf467ff355a13", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0806416202b69971446592511927fd35e2d3df53" +} +,{ + "testCaseDescription": "javascript-do-while-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Deleted the 'false' do/while statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Deleted the 'true' do/while statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 2, + 48 + ] + } + }, + "summary": "Added the 'false' do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "0806416202b69971446592511927fd35e2d3df53", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1310973b3dc9c6f7e0f20bb7842e869b5a355e7b" +} +,{ + "testCaseDescription": "javascript-do-while-statement-delete-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'true' do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "1310973b3dc9c6f7e0f20bb7842e869b5a355e7b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d0e72fbaf526e2beb6f4dbdbf8b91b972315ad91" +} +,{ + "testCaseDescription": "javascript-do-while-statement-delete-rest-test", + "expectedResult": { + "changes": { + "do-while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "do-while-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Deleted the 'false' do/while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "do-while-statement.js" + ], + "sha1": "d0e72fbaf526e2beb6f4dbdbf8b91b972315ad91", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a6c49cc7711970d9b1fdcfeef8ea1b312bcf0ace" +}] diff --git a/test/corpus/diff-summaries/javascript/false.json b/test/corpus/diff-summaries/javascript/false.json new file mode 100644 index 000000000..5d7396805 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/false.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-false-insert-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added 'false'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "d1241fa4218f33189f78a91a9513ca7e2120a2a0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5c3adaccd872d776c6b837d871a79cf1f0c520ec" +} +,{ + "testCaseDescription": "javascript-false-replacement-insert-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Added the 'false' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "false.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added 'false'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "5c3adaccd872d776c6b837d871a79cf1f0c520ec", + "gitDir": "test/corpus/repos/javascript", + "sha2": "791af8f5bd8ea06a1d83fe6a78788e02d2bb468d" +} +,{ + "testCaseDescription": "javascript-false-delete-insert-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added 'false'", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'false' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "791af8f5bd8ea06a1d83fe6a78788e02d2bb468d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "19b007fa1339fa0aa105833446507b6cc54688ad" +} +,{ + "testCaseDescription": "javascript-false-replacement-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Added the 'false' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted 'false'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "19b007fa1339fa0aa105833446507b6cc54688ad", + "gitDir": "test/corpus/repos/javascript", + "sha2": "de949429ff3d674e788d99101942f61de3beb083" +} +,{ + "testCaseDescription": "javascript-false-delete-replacement-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'false' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "false.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Deleted 'false'", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "false.js", + "end": [ + 2, + 14 + ] + } + }, + "summary": "Added the 'false' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "de949429ff3d674e788d99101942f61de3beb083", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a53c2421cba5ff7a05a70181604bae01a600aaa4" +} +,{ + "testCaseDescription": "javascript-false-delete-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted 'false'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "a53c2421cba5ff7a05a70181604bae01a600aaa4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "06a9f053e100d69f09fa0218b8cd1b815d55f820" +} +,{ + "testCaseDescription": "javascript-false-delete-rest-test", + "expectedResult": { + "changes": { + "false.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "false.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'false' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "false.js" + ], + "sha1": "06a9f053e100d69f09fa0218b8cd1b815d55f820", + "gitDir": "test/corpus/repos/javascript", + "sha2": "05ac6c8e85dcf3c89620fde92c3f7cccf4ca5d18" +}] diff --git a/test/corpus/diff-summaries/javascript/for-in-statement.json b/test/corpus/diff-summaries/javascript/for-in-statement.json new file mode 100644 index 000000000..8c37caf0e --- /dev/null +++ b/test/corpus/diff-summaries/javascript/for-in-statement.json @@ -0,0 +1,428 @@ +[{ + "testCaseDescription": "javascript-for-in-statement-insert-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 35 + ] + } + }, + "summary": "Added the 'thing in things' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "2017d7a8b91c62e06d4de3654b0a7a2d550e55b9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9af240cfa0f7af52df4650eddcac4bbd33dd5513" +} +,{ + "testCaseDescription": "javascript-for-in-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added the 'item in items' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 2, + 35 + ] + } + }, + "summary": "Added the 'thing in things' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "9af240cfa0f7af52df4650eddcac4bbd33dd5513", + "gitDir": "test/corpus/repos/javascript", + "sha2": "58da861d6aa35b1f3a741d2e32ecef9a23b3bfb9" +} +,{ + "testCaseDescription": "javascript-for-in-statement-delete-insert-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced the 'item' identifier with the 'thing' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 14 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 19 + ] + }, + { + "start": [ + 1, + 15 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'items' identifier with the 'things' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 23 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 27 + ] + }, + { + "start": [ + 1, + 25 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 30 + ] + } + ] + }, + "summary": "Replaced the 'item' identifier with the 'thing' identifier in the thing() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "58da861d6aa35b1f3a741d2e32ecef9a23b3bfb9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "37df916c1924ee482548cf1b653ca2f1adc897a4" +} +,{ + "testCaseDescription": "javascript-for-in-statement-replacement-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced the 'thing' identifier with the 'item' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 15 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 14 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 19 + ] + } + ] + }, + "summary": "Replaced the 'things' identifier with the 'items' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 25 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 30 + ] + }, + { + "start": [ + 1, + 23 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 27 + ] + } + ] + }, + "summary": "Replaced the 'thing' identifier with the 'item' identifier in the item() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "37df916c1924ee482548cf1b653ca2f1adc897a4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "517e2f1868a6cf33ab920bc26a84027328f44b55" +} +,{ + "testCaseDescription": "javascript-for-in-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'item in items' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 2, + 35 + ] + } + }, + "summary": "Deleted the 'thing in things' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added the 'item in items' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "517e2f1868a6cf33ab920bc26a84027328f44b55", + "gitDir": "test/corpus/repos/javascript", + "sha2": "095b4a966cb6a42a638f120901337fe3937afbfc" +} +,{ + "testCaseDescription": "javascript-for-in-statement-delete-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 35 + ] + } + }, + "summary": "Deleted the 'thing in things' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "095b4a966cb6a42a638f120901337fe3937afbfc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "994f9b8ba0c57e8397eb9bbdb74ac8503aeeb291" +} +,{ + "testCaseDescription": "javascript-for-in-statement-delete-rest-test", + "expectedResult": { + "changes": { + "for-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-in-statement.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'item in items' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-in-statement.js" + ], + "sha1": "994f9b8ba0c57e8397eb9bbdb74ac8503aeeb291", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2747446a2e77138d8a05f4ac9068b6c2fefe8c3d" +}] diff --git a/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json new file mode 100644 index 000000000..82d26afe0 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-for-loop-with-in-statement-insert-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 63 + ] + } + }, + "summary": "Added the 'key in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "faab59d023f70bb2d675e7d0671d36bc82dc9d0f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "184201b3796e0d955659a52b5d2b1624a9e68ef2" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 73 + ] + } + }, + "summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 2, + 63 + ] + } + }, + "summary": "Added the 'key in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "184201b3796e0d955659a52b5d2b1624a9e68ef2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "586a2c3efd9651e7be12ec5ef857b734daffea6a" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 14 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 9 + ] + } + ] + }, + "summary": "Replaced the 'otherKey' identifier with the 'key' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 52 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 68 + ] + }, + { + "start": [ + 1, + 47 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 58 + ] + } + ] + }, + "summary": "Replaced the 'doOtherSomething' identifier with the 'doSomething' identifier in the doSomething() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "586a2c3efd9651e7be12ec5ef857b734daffea6a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "fd27e1f30fd033a46ad5102fdcb5505937975f3d" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 9 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 14 + ] + } + ] + }, + "summary": "Replaced the 'key' identifier with the 'otherKey' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 47 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 58 + ] + }, + { + "start": [ + 1, + 52 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 68 + ] + } + ] + }, + "summary": "Replaced the 'doSomething' identifier with the 'doOtherSomething' identifier in the doOtherSomething() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "fd27e1f30fd033a46ad5102fdcb5505937975f3d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "39740a3c6176bf3db5c3574e1c6ca84608c315b1" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 73 + ] + } + }, + "summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 2, + 63 + ] + } + }, + "summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 2, + 73 + ] + } + }, + "summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "39740a3c6176bf3db5c3574e1c6ca84608c315b1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f438ed3707daff81f5e48c2726e9008707dd8a5a" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-delete-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 63 + ] + } + }, + "summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "f438ed3707daff81f5e48c2726e9008707dd8a5a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "90ed63f4489e99976afa912f90bfe0a3d89a7389" +} +,{ + "testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test", + "expectedResult": { + "changes": { + "for-loop-with-in-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-loop-with-in-statement.js", + "end": [ + 1, + 73 + ] + } + }, + "summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-loop-with-in-statement.js" + ], + "sha1": "90ed63f4489e99976afa912f90bfe0a3d89a7389", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0ba7c6b1f1b67daa1a4bea6a573c1b80be0cfbbc" +}] diff --git a/test/corpus/diff-summaries/javascript/for-of-statement.json b/test/corpus/diff-summaries/javascript/for-of-statement.json new file mode 100644 index 000000000..15e59c7e7 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/for-of-statement.json @@ -0,0 +1,428 @@ +[{ + "testCaseDescription": "javascript-for-of-statement-insert-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 43 + ] + } + }, + "summary": "Added the 'item of items' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "0ba7c6b1f1b67daa1a4bea6a573c1b80be0cfbbc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3d1449a3bc07b4ff653184c77efcc7eb72dd524c" +} +,{ + "testCaseDescription": "javascript-for-of-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Added the 'thing of things' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 2, + 43 + ] + } + }, + "summary": "Added the 'item of items' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "3d1449a3bc07b4ff653184c77efcc7eb72dd524c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "31112575f86e94f481e6eb6d74dabbfef5cf8ac6" +} +,{ + "testCaseDescription": "javascript-for-of-statement-delete-insert-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 15 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 14 + ] + } + ] + }, + "summary": "Replaced the 'thing' identifier with the 'item' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 19 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 18 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 23 + ] + } + ] + }, + "summary": "Replaced the 'things' identifier with the 'items' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 37 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 42 + ] + }, + { + "start": [ + 1, + 35 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 39 + ] + } + ] + }, + "summary": "Replaced the 'thing' identifier with the 'item' identifier in the process(item) function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "31112575f86e94f481e6eb6d74dabbfef5cf8ac6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bd5d2e141cbee15d933dcfe3eecf04cdda94f256" +} +,{ + "testCaseDescription": "javascript-for-of-statement-replacement-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 14 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 15 + ] + } + ] + }, + "summary": "Replaced the 'item' identifier with the 'thing' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 18 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 23 + ] + }, + { + "start": [ + 1, + 19 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'items' identifier with the 'things' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 35 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 39 + ] + }, + { + "start": [ + 1, + 37 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 42 + ] + } + ] + }, + "summary": "Replaced the 'item' identifier with the 'thing' identifier in the process(thing) function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "bd5d2e141cbee15d933dcfe3eecf04cdda94f256", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e868cdc733c04e540ccca5a4fd9b29055ff48b89" +} +,{ + "testCaseDescription": "javascript-for-of-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Deleted the 'thing of things' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 2, + 43 + ] + } + }, + "summary": "Deleted the 'item of items' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 2, + 46 + ] + } + }, + "summary": "Added the 'thing of things' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "e868cdc733c04e540ccca5a4fd9b29055ff48b89", + "gitDir": "test/corpus/repos/javascript", + "sha2": "eaa9c7d29fd865d30edc381723685ce4bdd3b3c0" +} +,{ + "testCaseDescription": "javascript-for-of-statement-delete-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 43 + ] + } + }, + "summary": "Deleted the 'item of items' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "eaa9c7d29fd865d30edc381723685ce4bdd3b3c0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "96274519618035299d535a46b5a9b09a88c624de" +} +,{ + "testCaseDescription": "javascript-for-of-statement-delete-rest-test", + "expectedResult": { + "changes": { + "for-of-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-of-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Deleted the 'thing of things' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-of-statement.js" + ], + "sha1": "96274519618035299d535a46b5a9b09a88c624de", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1e95946698829d93a91686c01b91618eb065b077" +}] diff --git a/test/corpus/diff-summaries/javascript/for-statement.json b/test/corpus/diff-summaries/javascript/for-statement.json new file mode 100644 index 000000000..05671f8d5 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/for-statement.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-for-statement-insert-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-statement.js", + "end": [ + 1, + 45 + ] + } + }, + "summary": "Added the 'i = 0, init(); i < 10; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "761990749004312c4b5e474eeacb839376523f0b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "720e97a0bc939ae883e7bbe18a84f02b8abeeb7a" +} +,{ + "testCaseDescription": "javascript-for-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "for-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Added the 'i = 0, init(); i < 100; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-statement.js", + "end": [ + 2, + 45 + ] + } + }, + "summary": "Added the 'i = 0, init(); i < 10; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "720e97a0bc939ae883e7bbe18a84f02b8abeeb7a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f4a0a3f223f66ace49c2e2894579639324035b85" +} +,{ + "testCaseDescription": "javascript-for-statement-delete-insert-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 25 + ], + "name": "for-statement.js", + "end": [ + 1, + 28 + ] + }, + { + "start": [ + 1, + 25 + ], + "name": "for-statement.js", + "end": [ + 1, + 27 + ] + } + ] + }, + "summary": "Replaced '100' with '10'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "f4a0a3f223f66ace49c2e2894579639324035b85", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b7aa4657257e1ff7e9018ca951c22d9c08f4ca5b" +} +,{ + "testCaseDescription": "javascript-for-statement-replacement-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 25 + ], + "name": "for-statement.js", + "end": [ + 1, + 27 + ] + }, + { + "start": [ + 1, + 25 + ], + "name": "for-statement.js", + "end": [ + 1, + 28 + ] + } + ] + }, + "summary": "Replaced '10' with '100'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "b7aa4657257e1ff7e9018ca951c22d9c08f4ca5b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d90fd03838f2ae92733c5d13db56c51f4dded714" +} +,{ + "testCaseDescription": "javascript-for-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "for-statement.js", + "end": [ + 2, + 45 + ] + } + }, + "summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "for-statement.js", + "end": [ + 2, + 46 + ] + } + }, + "summary": "Added the 'i = 0, init(); i < 100; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "d90fd03838f2ae92733c5d13db56c51f4dded714", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6a61a685e17ba55bf3982bab2b696346df632862" +} +,{ + "testCaseDescription": "javascript-for-statement-delete-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-statement.js", + "end": [ + 1, + 45 + ] + } + }, + "summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "6a61a685e17ba55bf3982bab2b696346df632862", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2bdadc3ac8ea4e15f6f2d7b4a9d1d2cf3b0a9567" +} +,{ + "testCaseDescription": "javascript-for-statement-delete-rest-test", + "expectedResult": { + "changes": { + "for-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "for-statement.js", + "end": [ + 1, + 46 + ] + } + }, + "summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "for-statement.js" + ], + "sha1": "2bdadc3ac8ea4e15f6f2d7b4a9d1d2cf3b0a9567", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e66aa2b6bacc2bbd796427540227b298518b1389" +}] diff --git a/test/corpus/diff-summaries/javascript/function-call-args.json b/test/corpus/diff-summaries/javascript/function-call-args.json new file mode 100644 index 000000000..3a990747e --- /dev/null +++ b/test/corpus/diff-summaries/javascript/function-call-args.json @@ -0,0 +1,608 @@ +[{ + "testCaseDescription": "javascript-function-call-args-insert-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function-call-args.js", + "end": [ + 1, + 77 + ] + } + }, + "summary": "Added the 'someFunction(1, \"string\", …, true)' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "101b21dd5ae54a69443d6899a30f575b0500e085", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0dc5c6df87d1ae60a9b4195126f2b0c70eecfc6e" +} +,{ + "testCaseDescription": "javascript-function-call-args-replacement-insert-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function-call-args.js", + "end": [ + 1, + 83 + ] + } + }, + "summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function-call-args.js", + "end": [ + 2, + 77 + ] + } + }, + "summary": "Added the 'someFunction(1, \"string\", …, true)' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "0dc5c6df87d1ae60a9b4195126f2b0c70eecfc6e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a10b3fa59ae8e50c1c0d6bc1a341eb31b41c6a9f" +} +,{ + "testCaseDescription": "javascript-function-call-args-delete-insert-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "function-call-args.js", + "end": [ + 1, + 30 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "function-call-args.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the \"otherString\" string with the \"string\" string in the someFunction(1, \"string\", …, true) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 41 + ], + "name": "function-call-args.js", + "end": [ + 1, + 42 + ] + }, + { + "start": [ + 1, + 36 + ], + "name": "function-call-args.js", + "end": [ + 1, + 37 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier in the someFunction(1, \"string\", …, true) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 43 + ], + "name": "function-call-args.js", + "end": [ + 1, + 44 + ] + }, + { + "start": [ + 1, + 38 + ], + "name": "function-call-args.js", + "end": [ + 1, + 39 + ] + } + ] + }, + "summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 60 + ], + "name": "function-call-args.js", + "end": [ + 1, + 61 + ] + }, + { + "start": [ + 1, + 55 + ], + "name": "function-call-args.js", + "end": [ + 1, + 56 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier in the console.log(a) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 71 + ], + "name": "function-call-args.js", + "end": [ + 1, + 72 + ] + }, + { + "start": [ + 1, + 66 + ], + "name": "function-call-args.js", + "end": [ + 1, + 67 + ] + } + ] + }, + "summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 77 + ], + "name": "function-call-args.js", + "end": [ + 1, + 82 + ] + }, + { + "start": [ + 1, + 72 + ], + "name": "function-call-args.js", + "end": [ + 1, + 76 + ] + } + ] + }, + "summary": "Replaced 'false' with 'true' in the someFunction(1, \"string\", …, true) function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "a10b3fa59ae8e50c1c0d6bc1a341eb31b41c6a9f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "940f6218f550757ae9d53a05ffe7d1893ceb085a" +} +,{ + "testCaseDescription": "javascript-function-call-args-replacement-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "function-call-args.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "function-call-args.js", + "end": [ + 1, + 30 + ] + } + ] + }, + "summary": "Replaced the \"string\" string with the \"otherString\" string in the someFunction(1, \"otherString\", …, false) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 36 + ], + "name": "function-call-args.js", + "end": [ + 1, + 37 + ] + }, + { + "start": [ + 1, + 41 + ], + "name": "function-call-args.js", + "end": [ + 1, + 42 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier in the someFunction(1, \"otherString\", …, false) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 38 + ], + "name": "function-call-args.js", + "end": [ + 1, + 39 + ] + }, + { + "start": [ + 1, + 43 + ], + "name": "function-call-args.js", + "end": [ + 1, + 44 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 55 + ], + "name": "function-call-args.js", + "end": [ + 1, + 56 + ] + }, + { + "start": [ + 1, + 60 + ], + "name": "function-call-args.js", + "end": [ + 1, + 61 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier in the console.log(b) method call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 66 + ], + "name": "function-call-args.js", + "end": [ + 1, + 67 + ] + }, + { + "start": [ + 1, + 71 + ], + "name": "function-call-args.js", + "end": [ + 1, + 72 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 72 + ], + "name": "function-call-args.js", + "end": [ + 1, + 76 + ] + }, + { + "start": [ + 1, + 77 + ], + "name": "function-call-args.js", + "end": [ + 1, + 82 + ] + } + ] + }, + "summary": "Replaced 'true' with 'false' in the someFunction(1, \"otherString\", …, false) function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "940f6218f550757ae9d53a05ffe7d1893ceb085a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7efa824b428048d98a2183fb8704105e37e8ac6e" +} +,{ + "testCaseDescription": "javascript-function-call-args-delete-replacement-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call-args.js", + "end": [ + 1, + 83 + ] + } + }, + "summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "function-call-args.js", + "end": [ + 2, + 77 + ] + } + }, + "summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function-call-args.js", + "end": [ + 2, + 83 + ] + } + }, + "summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "7efa824b428048d98a2183fb8704105e37e8ac6e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "375b6403b1b7e5fe2c26b799eeb8a097ae63c749" +} +,{ + "testCaseDescription": "javascript-function-call-args-delete-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call-args.js", + "end": [ + 1, + 77 + ] + } + }, + "summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "375b6403b1b7e5fe2c26b799eeb8a097ae63c749", + "gitDir": "test/corpus/repos/javascript", + "sha2": "62375666f152e860d0bdffdb49dcb981c5e77a1e" +} +,{ + "testCaseDescription": "javascript-function-call-args-delete-rest-test", + "expectedResult": { + "changes": { + "function-call-args.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call-args.js", + "end": [ + 1, + 83 + ] + } + }, + "summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call-args.js" + ], + "sha1": "62375666f152e860d0bdffdb49dcb981c5e77a1e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e5315f0371489f42d527c318faa1406833bb3c86" +}] diff --git a/test/corpus/diff-summaries/javascript/function-call.json b/test/corpus/diff-summaries/javascript/function-call.json new file mode 100644 index 000000000..a569ce162 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/function-call.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-function-call-insert-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Added the 'someFunction(arg1, \"arg2\")' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "cf31ddf834d011d1d55eee3da85c70f15eea67f1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "67d53107901a801fcd3027e5e0e5aae18fb2ca36" +} +,{ + "testCaseDescription": "javascript-function-call-replacement-insert-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Added the 'someFunction(arg1, \"arg3\")' function call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function-call.js", + "end": [ + 2, + 27 + ] + } + }, + "summary": "Added the 'someFunction(arg1, \"arg2\")' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "67d53107901a801fcd3027e5e0e5aae18fb2ca36", + "gitDir": "test/corpus/repos/javascript", + "sha2": "211596a53308346f468fe8ed76ace3ce30ddf4da" +} +,{ + "testCaseDescription": "javascript-function-call-delete-insert-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "function-call.js", + "end": [ + 1, + 26 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "function-call.js", + "end": [ + 1, + 26 + ] + } + ] + }, + "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the someFunction(arg1, \"arg2\") function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "211596a53308346f468fe8ed76ace3ce30ddf4da", + "gitDir": "test/corpus/repos/javascript", + "sha2": "fd80aa4f89fad9074132808237e195a8d9545b86" +} +,{ + "testCaseDescription": "javascript-function-call-replacement-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "function-call.js", + "end": [ + 1, + 26 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "function-call.js", + "end": [ + 1, + 26 + ] + } + ] + }, + "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the someFunction(arg1, \"arg3\") function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "fd80aa4f89fad9074132808237e195a8d9545b86", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9f9c596f918e7d7c6a538e6213855683eccd9dd7" +} +,{ + "testCaseDescription": "javascript-function-call-delete-replacement-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "function-call.js", + "end": [ + 2, + 27 + ] + } + }, + "summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function-call.js", + "end": [ + 2, + 27 + ] + } + }, + "summary": "Added the 'someFunction(arg1, \"arg3\")' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "9f9c596f918e7d7c6a538e6213855683eccd9dd7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "044ad612c7ddae2a92516fa81c38fe337f45f44b" +} +,{ + "testCaseDescription": "javascript-function-call-delete-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "044ad612c7ddae2a92516fa81c38fe337f45f44b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "245fd4ed85aa4fbcecaca43247ca77efa8382c34" +} +,{ + "testCaseDescription": "javascript-function-call-delete-rest-test", + "expectedResult": { + "changes": { + "function-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function-call.js", + "end": [ + 1, + 27 + ] + } + }, + "summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function-call.js" + ], + "sha1": "245fd4ed85aa4fbcecaca43247ca77efa8382c34", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1057513972364b1ca48ee19f74fb73ca06119e8c" +}] diff --git a/test/corpus/diff-summaries/javascript/function.json b/test/corpus/diff-summaries/javascript/function.json new file mode 100644 index 000000000..54a3fe590 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/function.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-function-insert-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Added an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "492ece78ac243f74d0f0bfce83c94b7162c1eaa6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a1e7c18328813b605f462f8909d48f17a8e0143b" +} +,{ + "testCaseDescription": "javascript-function-replacement-insert-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Added an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function.js", + "end": [ + 2, + 31 + ] + } + }, + "summary": "Added an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "a1e7c18328813b605f462f8909d48f17a8e0143b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2bf863a59e774f4350a3cdd80cf5dc5a491b7c7c" +} +,{ + "testCaseDescription": "javascript-function-delete-insert-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 24 + ], + "name": "function.js", + "end": [ + 1, + 28 + ] + }, + { + "start": [ + 1, + 24 + ], + "name": "function.js", + "end": [ + 1, + 28 + ] + } + ] + }, + "summary": "Replaced the 'arg1' identifier with the 'arg2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "2bf863a59e774f4350a3cdd80cf5dc5a491b7c7c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ccdde180a122687c848a953946552ab2e0e85f19" +} +,{ + "testCaseDescription": "javascript-function-replacement-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 24 + ], + "name": "function.js", + "end": [ + 1, + 28 + ] + }, + { + "start": [ + 1, + 24 + ], + "name": "function.js", + "end": [ + 1, + 28 + ] + } + ] + }, + "summary": "Replaced the 'arg2' identifier with the 'arg1' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "ccdde180a122687c848a953946552ab2e0e85f19", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2fc4cc2b1dd48ca880339b2e7bdcb80aa8474eab" +} +,{ + "testCaseDescription": "javascript-function-delete-replacement-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "function.js", + "end": [ + 2, + 31 + ] + } + }, + "summary": "Deleted an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "function.js", + "end": [ + 2, + 31 + ] + } + }, + "summary": "Added an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "2fc4cc2b1dd48ca880339b2e7bdcb80aa8474eab", + "gitDir": "test/corpus/repos/javascript", + "sha2": "265e835586016a3afaf60e97b0953a0e63a5908c" +} +,{ + "testCaseDescription": "javascript-function-delete-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "265e835586016a3afaf60e97b0953a0e63a5908c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9a2c09c340bccbd2ea80dbf353014da199f45840" +} +,{ + "testCaseDescription": "javascript-function-delete-rest-test", + "expectedResult": { + "changes": { + "function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted an anonymous(arg1, arg2) function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "function.js" + ], + "sha1": "9a2c09c340bccbd2ea80dbf353014da199f45840", + "gitDir": "test/corpus/repos/javascript", + "sha2": "142158e6e72a9a884b0d89c0b044b5c1473248db" +}] diff --git a/test/corpus/diff-summaries/javascript/generator-function.json b/test/corpus/diff-summaries/javascript/generator-function.json new file mode 100644 index 000000000..f9294a434 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/generator-function.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-generator-function-insert-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "generator-function.js", + "end": [ + 1, + 59 + ] + } + }, + "summary": "Added the 'generateStuff' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "304e0c432994c642daa18c284f4c1578416e77e1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a1f2e1505ff20196ae782ad0d4c5001bc2cc8cb1" +} +,{ + "testCaseDescription": "javascript-generator-function-replacement-insert-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "generator-function.js", + "end": [ + 1, + 62 + ] + } + }, + "summary": "Added the 'generateNewStuff' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "generator-function.js", + "end": [ + 2, + 59 + ] + } + }, + "summary": "Added the 'generateStuff' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "a1f2e1505ff20196ae782ad0d4c5001bc2cc8cb1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b4ca6466eb43270aca0908d03a0185180dc75011" +} +,{ + "testCaseDescription": "javascript-generator-function-delete-insert-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 11 + ], + "name": "generator-function.js", + "end": [ + 1, + 27 + ] + }, + { + "start": [ + 1, + 11 + ], + "name": "generator-function.js", + "end": [ + 1, + 24 + ] + } + ] + }, + "summary": "Replaced the 'generateNewStuff' identifier with the 'generateStuff' identifier in the generateStuff function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "b4ca6466eb43270aca0908d03a0185180dc75011", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c3a19c5bd3d78102ef15c6a49e8063940d9511ee" +} +,{ + "testCaseDescription": "javascript-generator-function-replacement-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 11 + ], + "name": "generator-function.js", + "end": [ + 1, + 24 + ] + }, + { + "start": [ + 1, + 11 + ], + "name": "generator-function.js", + "end": [ + 1, + 27 + ] + } + ] + }, + "summary": "Replaced the 'generateStuff' identifier with the 'generateNewStuff' identifier in the generateNewStuff function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "c3a19c5bd3d78102ef15c6a49e8063940d9511ee", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1d4670fa514b6e44c62cabb9de4cd8c565ac04ee" +} +,{ + "testCaseDescription": "javascript-generator-function-delete-replacement-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "generator-function.js", + "end": [ + 1, + 62 + ] + } + }, + "summary": "Deleted the 'generateNewStuff' function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "generator-function.js", + "end": [ + 2, + 59 + ] + } + }, + "summary": "Deleted the 'generateStuff' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "generator-function.js", + "end": [ + 2, + 62 + ] + } + }, + "summary": "Added the 'generateNewStuff' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "1d4670fa514b6e44c62cabb9de4cd8c565ac04ee", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a3f49a301897c265545ecb113bfdc96850ca29f1" +} +,{ + "testCaseDescription": "javascript-generator-function-delete-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "generator-function.js", + "end": [ + 1, + 59 + ] + } + }, + "summary": "Deleted the 'generateStuff' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "a3f49a301897c265545ecb113bfdc96850ca29f1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6d10fc13004f3500329c6bbae82678004ac0a103" +} +,{ + "testCaseDescription": "javascript-generator-function-delete-rest-test", + "expectedResult": { + "changes": { + "generator-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "generator-function.js", + "end": [ + 1, + 62 + ] + } + }, + "summary": "Deleted the 'generateNewStuff' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "generator-function.js" + ], + "sha1": "6d10fc13004f3500329c6bbae82678004ac0a103", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2f00ecb14d10a4cc210b7a56309fc75db90f3b64" +}] diff --git a/test/corpus/diff-summaries/javascript/identifier.json b/test/corpus/diff-summaries/javascript/identifier.json new file mode 100644 index 000000000..25f05ec96 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/identifier.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-identifier-insert-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "e117ae3f5e0945e0d8e971f7bbc0397229a45648", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0e588d86e85373e48c2f0698ec1f04561b9a24e2" +} +,{ + "testCaseDescription": "javascript-identifier-replacement-insert-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Added the 'theVar2' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "identifier.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "0e588d86e85373e48c2f0698ec1f04561b9a24e2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "304194727ea2932362b0d03d8f79a362974303ad" +} +,{ + "testCaseDescription": "javascript-identifier-delete-insert-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 8 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "304194727ea2932362b0d03d8f79a362974303ad", + "gitDir": "test/corpus/repos/javascript", + "sha2": "17438bcefeb350651ad9c920c65e6b8d21f3c157" +} +,{ + "testCaseDescription": "javascript-identifier-replacement-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 8 + ] + } + ] + }, + "summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "17438bcefeb350651ad9c920c65e6b8d21f3c157", + "gitDir": "test/corpus/repos/javascript", + "sha2": "db1afa5037ec331c9d2a490ec2c6052ed06235f8" +} +,{ + "testCaseDescription": "javascript-identifier-delete-replacement-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'theVar2' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "identifier.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Deleted the 'theVar' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "identifier.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Added the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "db1afa5037ec331c9d2a490ec2c6052ed06235f8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ab62284a2d89f526cdde80ad60e4f448a2376bed" +} +,{ + "testCaseDescription": "javascript-identifier-delete-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "ab62284a2d89f526cdde80ad60e4f448a2376bed", + "gitDir": "test/corpus/repos/javascript", + "sha2": "063615a0cbe20132f23e2f4ec74c4c10658840c6" +} +,{ + "testCaseDescription": "javascript-identifier-delete-rest-test", + "expectedResult": { + "changes": { + "identifier.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "identifier.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "identifier.js" + ], + "sha1": "063615a0cbe20132f23e2f4ec74c4c10658840c6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ebab90bd29d724f6dda4d39a32a6fa7d0b9adf52" +}] diff --git a/test/corpus/diff-summaries/javascript/if-else.json b/test/corpus/diff-summaries/javascript/if-else.json new file mode 100644 index 000000000..651c3ca00 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/if-else.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-if-else-insert-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 25 + ] + } + }, + "summary": "Added the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "805427c7aaf71a887c429562b647fe6811ba39c9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "46ab86718f54c48cd2f565a432f4187de5bc0fbe" +} +,{ + "testCaseDescription": "javascript-if-else-replacement-insert-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Added the 'a' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "if-else.js", + "end": [ + 2, + 25 + ] + } + }, + "summary": "Added the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "46ab86718f54c48cd2f565a432f4187de5bc0fbe", + "gitDir": "test/corpus/repos/javascript", + "sha2": "111b0fa6c30be41e42f49a8b97734c2f29ffe887" +} +,{ + "testCaseDescription": "javascript-if-else-delete-insert-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 29 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'a' if statement with the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "111b0fa6c30be41e42f49a8b97734c2f29ffe887", + "gitDir": "test/corpus/repos/javascript", + "sha2": "86bcc1f27f5c8d1108c1fd41681db0786ce40577" +} +,{ + "testCaseDescription": "javascript-if-else-replacement-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 29 + ] + } + ] + }, + "summary": "Replaced the 'x' if statement with the 'a' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "86bcc1f27f5c8d1108c1fd41681db0786ce40577", + "gitDir": "test/corpus/repos/javascript", + "sha2": "08b8b6246b046b2fa0a5b480bde9ea2a59496cab" +} +,{ + "testCaseDescription": "javascript-if-else-delete-replacement-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'a' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "if-else.js", + "end": [ + 2, + 25 + ] + } + }, + "summary": "Deleted the 'x' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "if-else.js", + "end": [ + 2, + 29 + ] + } + }, + "summary": "Added the 'a' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "08b8b6246b046b2fa0a5b480bde9ea2a59496cab", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f3c6acb380e4f8baa60d7ea87e7d62bdfb6832ac" +} +,{ + "testCaseDescription": "javascript-if-else-delete-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 25 + ] + } + }, + "summary": "Deleted the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "f3c6acb380e4f8baa60d7ea87e7d62bdfb6832ac", + "gitDir": "test/corpus/repos/javascript", + "sha2": "542ca4c9f7fdfd3e4660588a20f5cc7f40792166" +} +,{ + "testCaseDescription": "javascript-if-else-delete-rest-test", + "expectedResult": { + "changes": { + "if-else.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if-else.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'a' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if-else.js" + ], + "sha1": "542ca4c9f7fdfd3e4660588a20f5cc7f40792166", + "gitDir": "test/corpus/repos/javascript", + "sha2": "125f2e2e8e65a10784e72bb113319c805d4f42ac" +}] diff --git a/test/corpus/diff-summaries/javascript/if.json b/test/corpus/diff-summaries/javascript/if.json new file mode 100644 index 000000000..05a82ecd3 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/if.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-if-insert-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Added the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "408411b4e79d51cf3b50541c8d1115a3ce46dfa8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "66188f5ab8580e98c37f0b8702e95544551be755" +} +,{ + "testCaseDescription": "javascript-if-replacement-insert-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Added the 'a.b' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "if.js", + "end": [ + 2, + 19 + ] + } + }, + "summary": "Added the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "66188f5ab8580e98c37f0b8702e95544551be755", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0293e32d52fc191e4a768a91746259c99acc2342" +} +,{ + "testCaseDescription": "javascript-if-delete-insert-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 24 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 19 + ] + } + ] + }, + "summary": "Replaced the 'a.b' if statement with the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "0293e32d52fc191e4a768a91746259c99acc2342", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7dd98c9d586de0e61d3b80ac34fe25e4f89cab42" +} +,{ + "testCaseDescription": "javascript-if-replacement-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 19 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 24 + ] + } + ] + }, + "summary": "Replaced the 'x' if statement with the 'a.b' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "7dd98c9d586de0e61d3b80ac34fe25e4f89cab42", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9a8f836a101bdd5418634b5e762b9db21a91011c" +} +,{ + "testCaseDescription": "javascript-if-delete-replacement-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Deleted the 'a.b' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "if.js", + "end": [ + 2, + 19 + ] + } + }, + "summary": "Deleted the 'x' if statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "if.js", + "end": [ + 2, + 24 + ] + } + }, + "summary": "Added the 'a.b' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "9a8f836a101bdd5418634b5e762b9db21a91011c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "179c1b82b833c249afd123f342dfd06380b5acb8" +} +,{ + "testCaseDescription": "javascript-if-delete-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Deleted the 'x' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "179c1b82b833c249afd123f342dfd06380b5acb8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "95123146ceab7cf639e49adb97d36a8556c19940" +} +,{ + "testCaseDescription": "javascript-if-delete-rest-test", + "expectedResult": { + "changes": { + "if.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "if.js", + "end": [ + 1, + 24 + ] + } + }, + "summary": "Deleted the 'a.b' if statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "if.js" + ], + "sha1": "95123146ceab7cf639e49adb97d36a8556c19940", + "gitDir": "test/corpus/repos/javascript", + "sha2": "805427c7aaf71a887c429562b647fe6811ba39c9" +}] diff --git a/test/corpus/diff-summaries/javascript/math-assignment-operator.json b/test/corpus/diff-summaries/javascript/math-assignment-operator.json new file mode 100644 index 000000000..f66cfec7f --- /dev/null +++ b/test/corpus/diff-summaries/javascript/math-assignment-operator.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-math-assignment-operator-insert-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'x' math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "74f192419bb6a3a7ef68bb5eb4cf71e89e09b919", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d6da9771070c0da9787ae5e26c8914a45391d67b" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'x' math assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'x' math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "d6da9771070c0da9787ae5e26c8914a45391d67b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b817bac77a25047fc74bae958ac96e12e1f0a39e" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-delete-insert-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced '2' with '1' in the x math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "b817bac77a25047fc74bae958ac96e12e1f0a39e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4fe543b5777c4b39ffdeb2a4492405adc704d764" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-replacement-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced '1' with '2' in the x math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "4fe543b5777c4b39ffdeb2a4492405adc704d764", + "gitDir": "test/corpus/repos/javascript", + "sha2": "33afe3e3e1c77dabda9ec3e7b99f0c923bc23de5" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'x' math assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Deleted the 'x' math assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'x' math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "33afe3e3e1c77dabda9ec3e7b99f0c923bc23de5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3754066fb44624889e799c91af2a609fb1f1d27d" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-delete-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'x' math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "3754066fb44624889e799c91af2a609fb1f1d27d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bd1b94d3f2bf9806becf43c7f18927e1ff3932ec" +} +,{ + "testCaseDescription": "javascript-math-assignment-operator-delete-rest-test", + "expectedResult": { + "changes": { + "math-assignment-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-assignment-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'x' math assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-assignment-operator.js" + ], + "sha1": "bd1b94d3f2bf9806becf43c7f18927e1ff3932ec", + "gitDir": "test/corpus/repos/javascript", + "sha2": "faab59d023f70bb2d675e7d0671d36bc82dc9d0f" +}] diff --git a/test/corpus/diff-summaries/javascript/math-operator.json b/test/corpus/diff-summaries/javascript/math-operator.json new file mode 100644 index 000000000..5ed3ce26a --- /dev/null +++ b/test/corpus/diff-summaries/javascript/math-operator.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-math-operator-insert-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Added the 'i + j * 3 - j % 5' math operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "a871e92442fa237af75a13a311d49a15bcea9444", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6e6e7267c1e6bc551379dbdf39e3d4ca59d4a60c" +} +,{ + "testCaseDescription": "javascript-math-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Added the 'i + j * 2 - j % 4' math operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "math-operator.js", + "end": [ + 2, + 18 + ] + } + }, + "summary": "Added the 'i + j * 3 - j % 5' math operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "6e6e7267c1e6bc551379dbdf39e3d4ca59d4a60c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bf33c9910dcfad10ffafd330c0adff6b7a7f262a" +} +,{ + "testCaseDescription": "javascript-math-operator-delete-insert-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 9 + ], + "name": "math-operator.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 9 + ], + "name": "math-operator.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced '2' with '3'", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + ] + }, + "summary": "Replaced '4' with '5'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "bf33c9910dcfad10ffafd330c0adff6b7a7f262a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bd78c2dd93219f462c6a6823267bd327c14094db" +} +,{ + "testCaseDescription": "javascript-math-operator-replacement-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 9 + ], + "name": "math-operator.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 9 + ], + "name": "math-operator.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced '3' with '2'", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + ] + }, + "summary": "Replaced '5' with '4'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "bd78c2dd93219f462c6a6823267bd327c14094db", + "gitDir": "test/corpus/repos/javascript", + "sha2": "413c0d316184bb443b4facd4aec46b4b04f0df71" +} +,{ + "testCaseDescription": "javascript-math-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'i + j * 2 - j % 4' math operator", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "math-operator.js", + "end": [ + 2, + 18 + ] + } + }, + "summary": "Deleted the 'i + j * 3 - j % 5' math operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "math-operator.js", + "end": [ + 2, + 18 + ] + } + }, + "summary": "Added the 'i + j * 2 - j % 4' math operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "413c0d316184bb443b4facd4aec46b4b04f0df71", + "gitDir": "test/corpus/repos/javascript", + "sha2": "fb9ae3c73391e3158c898052fa343bb7bf98394b" +} +,{ + "testCaseDescription": "javascript-math-operator-delete-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'i + j * 3 - j % 5' math operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "fb9ae3c73391e3158c898052fa343bb7bf98394b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9d2684586034ffe1cd50891ac950f9bc2bf40d2e" +} +,{ + "testCaseDescription": "javascript-math-operator-delete-rest-test", + "expectedResult": { + "changes": { + "math-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "math-operator.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'i + j * 2 - j % 4' math operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "math-operator.js" + ], + "sha1": "9d2684586034ffe1cd50891ac950f9bc2bf40d2e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d7edfafd0028d88e036ad5af083bd4c0eaf821d5" +}] diff --git a/test/corpus/diff-summaries/javascript/member-access-assignment.json b/test/corpus/diff-summaries/javascript/member-access-assignment.json new file mode 100644 index 000000000..bd9029047 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/member-access-assignment.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-member-access-assignment-insert-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Added the 'y.x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "24ea895fcb8c904a8d057c536eb56be4a8928e33", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2b8bd487139dc144f01faab13961865c633bc0cd" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-replacement-insert-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Added the 'y.x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Added the 'y.x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "2b8bd487139dc144f01faab13961865c633bc0cd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "81f85cdb9f7a17a0560ee3e9d550eb3db0aaa739" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-delete-insert-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 7 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + }, + { + "start": [ + 1, + 7 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + ] + }, + "summary": "Replaced '1' with '0' in an assignment to y.x", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "81f85cdb9f7a17a0560ee3e9d550eb3db0aaa739", + "gitDir": "test/corpus/repos/javascript", + "sha2": "30285e2a6c2057ad1af3e8475aa48d75c6e11199" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-replacement-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 7 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + }, + { + "start": [ + 1, + 7 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + ] + }, + "summary": "Replaced '0' with '1' in an assignment to y.x", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "30285e2a6c2057ad1af3e8475aa48d75c6e11199", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a2a7e40667563b5b73dcafcbb1e476e9bd2454ba" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-delete-replacement-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'y.x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Deleted the 'y.x' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Added the 'y.x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "a2a7e40667563b5b73dcafcbb1e476e9bd2454ba", + "gitDir": "test/corpus/repos/javascript", + "sha2": "fd07c5983ef2c5a8857943d86f1df8f7090a4edd" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-delete-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'y.x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "fd07c5983ef2c5a8857943d86f1df8f7090a4edd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c9211034900804da82ade93b31c9ea5dfdbfcd35" +} +,{ + "testCaseDescription": "javascript-member-access-assignment-delete-rest-test", + "expectedResult": { + "changes": { + "member-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access-assignment.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'y.x' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access-assignment.js" + ], + "sha1": "c9211034900804da82ade93b31c9ea5dfdbfcd35", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0286a0f0ca80520eb670a372dbf844ec8357639e" +}] diff --git a/test/corpus/diff-summaries/javascript/member-access.json b/test/corpus/diff-summaries/javascript/member-access.json new file mode 100644 index 000000000..b9a2d8e22 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/member-access.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-member-access-insert-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "member-access.js", + "end": [ + 1, + 15 + ] + } + }, + "summary": "Added the 'x.someProperty' member access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "6efc7d3ef6f891602e19a27ed0c598e6c5e179ea", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4c558b5d02c5e2d435f6a4bbfda3da186aa580b0" +} +,{ + "testCaseDescription": "javascript-member-access-replacement-insert-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "member-access.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Added the 'x.someOtherProperty' member access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "member-access.js", + "end": [ + 2, + 15 + ] + } + }, + "summary": "Added the 'x.someProperty' member access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "4c558b5d02c5e2d435f6a4bbfda3da186aa580b0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ba2f36530d6780fd4b48247d4e07495ab99ff849" +} +,{ + "testCaseDescription": "javascript-member-access-delete-insert-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "member-access.js", + "end": [ + 1, + 20 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "member-access.js", + "end": [ + 1, + 15 + ] + } + ] + }, + "summary": "Replaced the 'someOtherProperty' identifier with the 'someProperty' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "ba2f36530d6780fd4b48247d4e07495ab99ff849", + "gitDir": "test/corpus/repos/javascript", + "sha2": "236df8848d358b1867fec80674da98c30a21fa4f" +} +,{ + "testCaseDescription": "javascript-member-access-replacement-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "member-access.js", + "end": [ + 1, + 15 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "member-access.js", + "end": [ + 1, + 20 + ] + } + ] + }, + "summary": "Replaced the 'someProperty' identifier with the 'someOtherProperty' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "236df8848d358b1867fec80674da98c30a21fa4f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7f5877fc43be3f38c976057116b85bd9e54f4c90" +} +,{ + "testCaseDescription": "javascript-member-access-delete-replacement-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Deleted the 'x.someOtherProperty' member access", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "member-access.js", + "end": [ + 2, + 15 + ] + } + }, + "summary": "Deleted the 'x.someProperty' member access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "member-access.js", + "end": [ + 2, + 20 + ] + } + }, + "summary": "Added the 'x.someOtherProperty' member access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "7f5877fc43be3f38c976057116b85bd9e54f4c90", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5db12107fe6a175ade7fbff6b24b9d5d32a81ac7" +} +,{ + "testCaseDescription": "javascript-member-access-delete-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access.js", + "end": [ + 1, + 15 + ] + } + }, + "summary": "Deleted the 'x.someProperty' member access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "5db12107fe6a175ade7fbff6b24b9d5d32a81ac7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "32fa045d3b6ae515ff252d024963fa53f469ecf2" +} +,{ + "testCaseDescription": "javascript-member-access-delete-rest-test", + "expectedResult": { + "changes": { + "member-access.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "member-access.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Deleted the 'x.someOtherProperty' member access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "member-access.js" + ], + "sha1": "32fa045d3b6ae515ff252d024963fa53f469ecf2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c77d21ce31ff19818614b186e90aa577cc20ce9d" +}] diff --git a/test/corpus/diff-summaries/javascript/method-call.json b/test/corpus/diff-summaries/javascript/method-call.json new file mode 100644 index 000000000..0d440888f --- /dev/null +++ b/test/corpus/diff-summaries/javascript/method-call.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-method-call-insert-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "method-call.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "1057513972364b1ca48ee19f74fb73ca06119e8c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e331bc52539866046826efc023575d5fd3db6165" +} +,{ + "testCaseDescription": "javascript-method-call-replacement-insert-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "method-call.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "method-call.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "e331bc52539866046826efc023575d5fd3db6165", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bd24f5dadbf7a65bd231a338e6159df321dd57f5" +} +,{ + "testCaseDescription": "javascript-method-call-delete-insert-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 25 + ], + "name": "method-call.js", + "end": [ + 1, + 31 + ] + }, + { + "start": [ + 1, + 25 + ], + "name": "method-call.js", + "end": [ + 1, + 31 + ] + } + ] + }, + "summary": "Replaced the \"arg3\" string with the \"arg2\" string in the object.someMethod(arg1, \"arg2\") method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "bd24f5dadbf7a65bd231a338e6159df321dd57f5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "13271135545e9d65b6ff2a4c7c28616aad1184e6" +} +,{ + "testCaseDescription": "javascript-method-call-replacement-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 25 + ], + "name": "method-call.js", + "end": [ + 1, + 31 + ] + }, + { + "start": [ + 1, + 25 + ], + "name": "method-call.js", + "end": [ + 1, + 31 + ] + } + ] + }, + "summary": "Replaced the \"arg2\" string with the \"arg3\" string in the object.someMethod(arg1, \"arg3\") method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "13271135545e9d65b6ff2a4c7c28616aad1184e6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1c29343f384ab78feb8d55b28d06ca5b2c2a1543" +} +,{ + "testCaseDescription": "javascript-method-call-delete-replacement-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "method-call.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "method-call.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "method-call.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "1c29343f384ab78feb8d55b28d06ca5b2c2a1543", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f61923d7461a07df3744705230e56b12f0b2d216" +} +,{ + "testCaseDescription": "javascript-method-call-delete-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "method-call.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "f61923d7461a07df3744705230e56b12f0b2d216", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5f7fc9da90b24df9a9ad1ff1eae1b3a00657f16e" +} +,{ + "testCaseDescription": "javascript-method-call-delete-rest-test", + "expectedResult": { + "changes": { + "method-call.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "method-call.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "method-call.js" + ], + "sha1": "5f7fc9da90b24df9a9ad1ff1eae1b3a00657f16e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "101b21dd5ae54a69443d6899a30f575b0500e085" +}] diff --git a/test/corpus/diff-summaries/javascript/named-function.json b/test/corpus/diff-summaries/javascript/named-function.json new file mode 100644 index 000000000..447fd80fc --- /dev/null +++ b/test/corpus/diff-summaries/javascript/named-function.json @@ -0,0 +1,444 @@ +[{ + "testCaseDescription": "javascript-named-function-insert-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "named-function.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Added the 'myFunction' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "2f00ecb14d10a4cc210b7a56309fc75db90f3b64", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e87e0464ade6d9ccfcf8858e8360eed0892ac9d2" +} +,{ + "testCaseDescription": "javascript-named-function-replacement-insert-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "named-function.js", + "end": [ + 1, + 45 + ] + } + }, + "summary": "Added the 'anotherFunction' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "named-function.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Added the 'myFunction' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "e87e0464ade6d9ccfcf8858e8360eed0892ac9d2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "233d845790d1fb1c6914aa56ee916044c1491955" +} +,{ + "testCaseDescription": "javascript-named-function-delete-insert-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "named-function.js", + "end": [ + 1, + 25 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "named-function.js", + "end": [ + 1, + 20 + ] + } + ] + }, + "summary": "Replaced the 'anotherFunction' identifier with the 'myFunction' identifier in the myFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 21 + ], + "name": "named-function.js", + "end": [ + 1, + 25 + ] + } + }, + "summary": "Added the 'arg1' identifier in the myFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 27 + ], + "name": "named-function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Added the 'arg2' identifier in the myFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 35 + ], + "name": "named-function.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Added the 'arg2' identifier in the myFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 30 + ], + "name": "named-function.js", + "end": [ + 1, + 43 + ] + } + }, + "summary": "Deleted the 'false' return statement in the myFunction function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "233d845790d1fb1c6914aa56ee916044c1491955", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6591af1b718467293fb40094d31d8bcd1bc0a679" +} +,{ + "testCaseDescription": "javascript-named-function-replacement-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "named-function.js", + "end": [ + 1, + 20 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "named-function.js", + "end": [ + 1, + 25 + ] + } + ] + }, + "summary": "Replaced the 'myFunction' identifier with the 'anotherFunction' identifier in the anotherFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 21 + ], + "name": "named-function.js", + "end": [ + 1, + 25 + ] + } + }, + "summary": "Deleted the 'arg1' identifier in the anotherFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 27 + ], + "name": "named-function.js", + "end": [ + 1, + 31 + ] + } + }, + "summary": "Deleted the 'arg2' identifier in the anotherFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 30 + ], + "name": "named-function.js", + "end": [ + 1, + 43 + ] + } + }, + "summary": "Added the 'false' return statement in the anotherFunction function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 35 + ], + "name": "named-function.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Deleted the 'arg2' identifier in the anotherFunction function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "6591af1b718467293fb40094d31d8bcd1bc0a679", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ea7b2d944b9f4b906b750883dc50754096ac197d" +} +,{ + "testCaseDescription": "javascript-named-function-delete-replacement-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "named-function.js", + "end": [ + 1, + 45 + ] + } + }, + "summary": "Deleted the 'anotherFunction' function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "named-function.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Deleted the 'myFunction' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "named-function.js", + "end": [ + 2, + 45 + ] + } + }, + "summary": "Added the 'anotherFunction' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "ea7b2d944b9f4b906b750883dc50754096ac197d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d5d86035b6457b7e1f55cbe249d2f36cca54ca86" +} +,{ + "testCaseDescription": "javascript-named-function-delete-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "named-function.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'myFunction' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "d5d86035b6457b7e1f55cbe249d2f36cca54ca86", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ac73db0211c8b73c9ce79a3c730606fdfca84dbe" +} +,{ + "testCaseDescription": "javascript-named-function-delete-rest-test", + "expectedResult": { + "changes": { + "named-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "named-function.js", + "end": [ + 1, + 45 + ] + } + }, + "summary": "Deleted the 'anotherFunction' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "named-function.js" + ], + "sha1": "ac73db0211c8b73c9ce79a3c730606fdfca84dbe", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6efc7d3ef6f891602e19a27ed0c598e6c5e179ea" +}] diff --git a/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json b/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json new file mode 100644 index 000000000..6f459bbf9 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/nested-do-while-in-function.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-nested-do-while-in-function-insert-test", + "expectedResult": { + "changes": { + "nested-do-while-in-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 65 + ] + } + }, + "summary": "Added the 'f' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-do-while-in-function.js" + ], + "sha1": "70ec1b887cd3227d1db143720c9f83c6aee76857", + "gitDir": "test/corpus/repos/javascript", + "sha2": "40718757d69121812c5a1b88b6b254d91fff927d" +} +,{ + "testCaseDescription": "javascript-nested-do-while-in-function-replacement-insert-test", + "expectedResult": { + "changes": { + "nested-do-while-in-function.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 65 + ] + } + }, + "summary": "Added the 'f' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 2, + 65 + ] + } + }, + "summary": "Added the 'f' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-do-while-in-function.js" + ], + "sha1": "40718757d69121812c5a1b88b6b254d91fff927d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f62ea5ca3fd0fa46620b5e5794eb8e70b1699e51" +} +,{ + "testCaseDescription": "javascript-nested-do-while-in-function-delete-insert-test", + "expectedResult": { + "changes": { + "nested-do-while-in-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 41 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 45 + ] + }, + { + "start": [ + 1, + 41 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 45 + ] + } + ] + }, + "summary": "Replaced the 'arg2' identifier with the 'arg1' identifier in the something(arg1) function call of the 'f' function", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 57 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 61 + ] + }, + { + "start": [ + 1, + 57 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 61 + ] + } + ] + }, + "summary": "Replaced the 'arg1' identifier with the 'arg2' identifier in the arg2 do/while statement of the 'f' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-do-while-in-function.js" + ], + "sha1": "f62ea5ca3fd0fa46620b5e5794eb8e70b1699e51", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c89b566e205a722065b4898e103cb48518469ae4" +} +,{ + "testCaseDescription": "javascript-nested-do-while-in-function-replacement-test", + "expectedResult": { + "changes": { + "nested-do-while-in-function.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 41 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 45 + ] + }, + { + "start": [ + 1, + 41 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 45 + ] + } + ] + }, + "summary": "Replaced the 'arg1' identifier with the 'arg2' identifier in the something(arg2) function call of the 'f' function", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 57 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 61 + ] + }, + { + "start": [ + 1, + 57 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 61 + ] + } + ] + }, + "summary": "Replaced the 'arg2' identifier with the 'arg1' identifier in the arg1 do/while statement of the 'f' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-do-while-in-function.js" + ], + "sha1": "c89b566e205a722065b4898e103cb48518469ae4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f56c46085db0b8db31cfa4540af347117d489e8b" +} +,{ + "testCaseDescription": "javascript-nested-do-while-in-function-delete-replacement-test", + "expectedResult": { + "changes": { + "nested-do-while-in-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 65 + ] + } + }, + "summary": "Deleted the 'f' function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 2, + 65 + ] + } + }, + "summary": "Deleted the 'f' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 2, + 65 + ] + } + }, + "summary": "Added the 'f' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-do-while-in-function.js" + ], + "sha1": "f56c46085db0b8db31cfa4540af347117d489e8b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c3a81eba697a0b359b9a762fed814b36cafd9f0f" +} +,{ + "testCaseDescription": "javascript-nested-do-while-in-function-delete-test", + "expectedResult": { + "changes": { + "nested-do-while-in-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 65 + ] + } + }, + "summary": "Deleted the 'f' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-do-while-in-function.js" + ], + "sha1": "c3a81eba697a0b359b9a762fed814b36cafd9f0f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4278eca970eb128b7ea79e9b227763b4726f3acd" +} +,{ + "testCaseDescription": "javascript-nested-do-while-in-function-delete-rest-test", + "expectedResult": { + "changes": { + "nested-do-while-in-function.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "nested-do-while-in-function.js", + "end": [ + 1, + 65 + ] + } + }, + "summary": "Deleted the 'f' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-do-while-in-function.js" + ], + "sha1": "4278eca970eb128b7ea79e9b227763b4726f3acd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "14310ea870b177f2187e152498699c8cd1b039f3" +}] diff --git a/test/corpus/diff-summaries/javascript/nested-functions.json b/test/corpus/diff-summaries/javascript/nested-functions.json new file mode 100644 index 000000000..643c18f23 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/nested-functions.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-nested-functions-insert-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "nested-functions.js", + "end": [ + 1, + 103 + ] + } + }, + "summary": "Added the 'parent' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "2747446a2e77138d8a05f4ac9068b6c2fefe8c3d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "dc05fc47073a90674b27dd52f2e20157d4bbb692" +} +,{ + "testCaseDescription": "javascript-nested-functions-replacement-insert-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "nested-functions.js", + "end": [ + 1, + 103 + ] + } + }, + "summary": "Added the 'parent' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "nested-functions.js", + "end": [ + 2, + 103 + ] + } + }, + "summary": "Added the 'parent' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "dc05fc47073a90674b27dd52f2e20157d4bbb692", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ceda9837fa4d5f417bc943f0df77c878b51e4620" +} +,{ + "testCaseDescription": "javascript-nested-functions-delete-insert-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 74 + ], + "name": "nested-functions.js", + "end": [ + 1, + 78 + ] + }, + { + "start": [ + 1, + 74 + ], + "name": "nested-functions.js", + "end": [ + 1, + 78 + ] + } + ] + }, + "summary": "Replaced the 'arg1' identifier with the 'arg3' identifier in the console.log(arg3) method call of the 'child' function", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 93 + ], + "name": "nested-functions.js", + "end": [ + 1, + 97 + ] + }, + { + "start": [ + 1, + 93 + ], + "name": "nested-functions.js", + "end": [ + 1, + 97 + ] + } + ] + }, + "summary": "Replaced the 'arg2' identifier with the 'arg4' identifier in the console.log(arg4) method call of the 'child' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "ceda9837fa4d5f417bc943f0df77c878b51e4620", + "gitDir": "test/corpus/repos/javascript", + "sha2": "31c2d106f210aa5efc7ffc2d638d12ad48229812" +} +,{ + "testCaseDescription": "javascript-nested-functions-replacement-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 74 + ], + "name": "nested-functions.js", + "end": [ + 1, + 78 + ] + }, + { + "start": [ + 1, + 74 + ], + "name": "nested-functions.js", + "end": [ + 1, + 78 + ] + } + ] + }, + "summary": "Replaced the 'arg3' identifier with the 'arg1' identifier in the console.log(arg1) method call of the 'child' function", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 93 + ], + "name": "nested-functions.js", + "end": [ + 1, + 97 + ] + }, + { + "start": [ + 1, + 93 + ], + "name": "nested-functions.js", + "end": [ + 1, + 97 + ] + } + ] + }, + "summary": "Replaced the 'arg4' identifier with the 'arg2' identifier in the console.log(arg2) method call of the 'child' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "31c2d106f210aa5efc7ffc2d638d12ad48229812", + "gitDir": "test/corpus/repos/javascript", + "sha2": "98eb2195462290eb69d5a2a744c9d1979899bbe8" +} +,{ + "testCaseDescription": "javascript-nested-functions-delete-replacement-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "nested-functions.js", + "end": [ + 1, + 103 + ] + } + }, + "summary": "Deleted the 'parent' function", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "nested-functions.js", + "end": [ + 2, + 103 + ] + } + }, + "summary": "Deleted the 'parent' function", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "nested-functions.js", + "end": [ + 2, + 103 + ] + } + }, + "summary": "Added the 'parent' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "98eb2195462290eb69d5a2a744c9d1979899bbe8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f6573d0d559b96309ebf0d5079e43976d0bc7fe8" +} +,{ + "testCaseDescription": "javascript-nested-functions-delete-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "nested-functions.js", + "end": [ + 1, + 103 + ] + } + }, + "summary": "Deleted the 'parent' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "f6573d0d559b96309ebf0d5079e43976d0bc7fe8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "23cf31d25f6690285855642d7471b14c8c0679b0" +} +,{ + "testCaseDescription": "javascript-nested-functions-delete-rest-test", + "expectedResult": { + "changes": { + "nested-functions.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "nested-functions.js", + "end": [ + 1, + 103 + ] + } + }, + "summary": "Deleted the 'parent' function", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "nested-functions.js" + ], + "sha1": "23cf31d25f6690285855642d7471b14c8c0679b0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "70ec1b887cd3227d1db143720c9f83c6aee76857" +}] diff --git a/test/corpus/diff-summaries/javascript/null.json b/test/corpus/diff-summaries/javascript/null.json new file mode 100644 index 000000000..487cef6ee --- /dev/null +++ b/test/corpus/diff-summaries/javascript/null.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-null-insert-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added the 'null' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "11a27a81f8e7e33aac2eb0844d3465acf8f9bb0d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "eb6644a70a4cd3a9d3cc65812e3ac5c1a4d76520" +} +,{ + "testCaseDescription": "javascript-null-replacement-insert-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'null' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "null.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Added the 'null' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "eb6644a70a4cd3a9d3cc65812e3ac5c1a4d76520", + "gitDir": "test/corpus/repos/javascript", + "sha2": "94a5c1d61909967783e1c9acca96fdf47cde7f3e" +} +,{ + "testCaseDescription": "javascript-null-delete-insert-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added the 'null' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'null' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "94a5c1d61909967783e1c9acca96fdf47cde7f3e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5dcff49942934eff57dac635ed367b34a9579c9c" +} +,{ + "testCaseDescription": "javascript-null-replacement-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'null' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted the 'null' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "5dcff49942934eff57dac635ed367b34a9579c9c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "606f0007b3d2e0c89cce1fbc92d0fbbeaff87c11" +} +,{ + "testCaseDescription": "javascript-null-delete-replacement-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'null' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "null.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Deleted the 'null' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "null.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Added the 'null' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "606f0007b3d2e0c89cce1fbc92d0fbbeaff87c11", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1142c2c15d6730bb2bfa0be5f76115ca4667064c" +} +,{ + "testCaseDescription": "javascript-null-delete-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted the 'null' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "1142c2c15d6730bb2bfa0be5f76115ca4667064c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "74f6868171e2ab7e8a4e77d6b07d1e7c1dcb6b07" +} +,{ + "testCaseDescription": "javascript-null-delete-rest-test", + "expectedResult": { + "changes": { + "null.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "null.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'null' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "null.js" + ], + "sha1": "74f6868171e2ab7e8a4e77d6b07d1e7c1dcb6b07", + "gitDir": "test/corpus/repos/javascript", + "sha2": "43fd131de0f55fa1826e3fa3b95b88b7ba74fd68" +}] diff --git a/test/corpus/diff-summaries/javascript/number.json b/test/corpus/diff-summaries/javascript/number.json new file mode 100644 index 000000000..9699bd31a --- /dev/null +++ b/test/corpus/diff-summaries/javascript/number.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-number-insert-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + }, + "summary": "Added '101'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "6353fa1218bad4624b606cf46bfcd6c18d1e13c2", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7c7876c3c6be4f9f70b5b83ea763df7301fcd684" +} +,{ + "testCaseDescription": "javascript-number-replacement-insert-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + }, + "summary": "Added '102'", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "number.js", + "end": [ + 2, + 4 + ] + } + }, + "summary": "Added '101'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "7c7876c3c6be4f9f70b5b83ea763df7301fcd684", + "gitDir": "test/corpus/repos/javascript", + "sha2": "504616415391cd15d571dad61cf0df37572cc9a9" +} +,{ + "testCaseDescription": "javascript-number-delete-insert-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + ] + }, + "summary": "Replaced '102' with '101'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "504616415391cd15d571dad61cf0df37572cc9a9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "63450eae5510a793bdf738ccd7956bce348ce393" +} +,{ + "testCaseDescription": "javascript-number-replacement-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + ] + }, + "summary": "Replaced '101' with '102'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "63450eae5510a793bdf738ccd7956bce348ce393", + "gitDir": "test/corpus/repos/javascript", + "sha2": "db793bae2da69d2c4d00dd90611a9cd5913a5efc" +} +,{ + "testCaseDescription": "javascript-number-delete-replacement-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + }, + "summary": "Deleted '102'", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "number.js", + "end": [ + 2, + 4 + ] + } + }, + "summary": "Deleted '101'", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "number.js", + "end": [ + 2, + 4 + ] + } + }, + "summary": "Added '102'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "db793bae2da69d2c4d00dd90611a9cd5913a5efc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0c5dcd56a648d9cf91377e14604afa2f64ca6738" +} +,{ + "testCaseDescription": "javascript-number-delete-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + }, + "summary": "Deleted '101'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "0c5dcd56a648d9cf91377e14604afa2f64ca6738", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ccdba59644ee3190b25f1975f8ef24c0d0a39a1c" +} +,{ + "testCaseDescription": "javascript-number-delete-rest-test", + "expectedResult": { + "changes": { + "number.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "number.js", + "end": [ + 1, + 4 + ] + } + }, + "summary": "Deleted '102'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "number.js" + ], + "sha1": "ccdba59644ee3190b25f1975f8ef24c0d0a39a1c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7cd0762fb1e84cad3dcf9a1c41b07c8112c888fd" +}] diff --git a/test/corpus/diff-summaries/javascript/object-with-methods.json b/test/corpus/diff-summaries/javascript/object-with-methods.json new file mode 100644 index 000000000..75daf0972 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/object-with-methods.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-objects-with-methods-insert-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added the '{ add }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "59872fcdcee9cd22104933bbc925d9987cd393b6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b3aa3244e4a63ad27cee5f101e357a16bbb6e3b5" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-replacement-insert-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 37 + ] + } + }, + "summary": "Added the '{ subtract }' object", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added the '{ add }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "b3aa3244e4a63ad27cee5f101e357a16bbb6e3b5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8dbd1ca6c20e067e9a66b00e6e9eb883d0ee3635" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-delete-insert-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 6 + ] + } + ] + }, + "summary": "Replaced the 'subtract' identifier with the 'add' identifier in the add method", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "8dbd1ca6c20e067e9a66b00e6e9eb883d0ee3635", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e14f2325776fdfc3c455b97c477dda641cf9fa04" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-replacement-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 6 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced the 'add' identifier with the 'subtract' identifier in the subtract method", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "e14f2325776fdfc3c455b97c477dda641cf9fa04", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7b8889fcf97d4f9b27d986f7dbedea7ab1b737d0" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-delete-replacement-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 37 + ] + } + }, + "summary": "Deleted the '{ subtract }' object", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Deleted the '{ add }' object", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 2, + 37 + ] + } + }, + "summary": "Added the '{ subtract }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "7b8889fcf97d4f9b27d986f7dbedea7ab1b737d0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d731aac66d17f598fc601b02c4ad03adff3a3bae" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-delete-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the '{ add }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "d731aac66d17f598fc601b02c4ad03adff3a3bae", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f2ac6622cd2122b9163f11890d688ac53a9bd01e" +} +,{ + "testCaseDescription": "javascript-objects-with-methods-delete-rest-test", + "expectedResult": { + "changes": { + "objects-with-methods.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "objects-with-methods.js", + "end": [ + 1, + 37 + ] + } + }, + "summary": "Deleted the '{ subtract }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "objects-with-methods.js" + ], + "sha1": "f2ac6622cd2122b9163f11890d688ac53a9bd01e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "71a215c337687c245da7c6eafcba311e3ba0e09b" +}] diff --git a/test/corpus/diff-summaries/javascript/object.json b/test/corpus/diff-summaries/javascript/object.json new file mode 100644 index 000000000..747e61990 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/object.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-object-insert-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "object.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Added the '{ \"key1\": … }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "851fcf30f6f5512f49a59cc7167c684cdf668576", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8e2ca717edb3e850c87a7a5d0f4299018e008adb" +} +,{ + "testCaseDescription": "javascript-object-replacement-insert-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "object.js", + "end": [ + 1, + 54 + ] + } + }, + "summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "object.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Added the '{ \"key1\": … }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "8e2ca717edb3e850c87a7a5d0f4299018e008adb", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9984c70968070ad662bff6c3b00840bfaf8c1230" +} +,{ + "testCaseDescription": "javascript-object-delete-insert-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "this": { + "start": [ + 1, + 21 + ], + "name": "object.js", + "end": [ + 1, + 37 + ] + } + }, + "summary": "Deleted the '\"key2\": …' pair", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 39 + ], + "name": "object.js", + "end": [ + 1, + 52 + ] + } + }, + "summary": "Deleted the '\"key3\": …' pair", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "9984c70968070ad662bff6c3b00840bfaf8c1230", + "gitDir": "test/corpus/repos/javascript", + "sha2": "34a57cf66174002c4cb01bc2cde145af45c79bd1" +} +,{ + "testCaseDescription": "javascript-object-replacement-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "that": { + "start": [ + 1, + 21 + ], + "name": "object.js", + "end": [ + 1, + 37 + ] + } + }, + "summary": "Added the '\"key2\": …' pair", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 39 + ], + "name": "object.js", + "end": [ + 1, + 52 + ] + } + }, + "summary": "Added the '\"key3\": …' pair", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "34a57cf66174002c4cb01bc2cde145af45c79bd1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "5212b2d89e443b54f3fa34e7f52123fe152bed71" +} +,{ + "testCaseDescription": "javascript-object-delete-replacement-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "object.js", + "end": [ + 1, + 54 + ] + } + }, + "summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "object.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Deleted the '{ \"key1\": … }' object", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "object.js", + "end": [ + 2, + 54 + ] + } + }, + "summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "5212b2d89e443b54f3fa34e7f52123fe152bed71", + "gitDir": "test/corpus/repos/javascript", + "sha2": "aa3e5600050b3762cdf02c85bdd7c6c91c52896e" +} +,{ + "testCaseDescription": "javascript-object-delete-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "object.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the '{ \"key1\": … }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "aa3e5600050b3762cdf02c85bdd7c6c91c52896e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ffbe546c27f8f46e1c56d5d60f298870b4afe943" +} +,{ + "testCaseDescription": "javascript-object-delete-rest-test", + "expectedResult": { + "changes": { + "object.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "object.js", + "end": [ + 1, + 54 + ] + } + }, + "summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "object.js" + ], + "sha1": "ffbe546c27f8f46e1c56d5d60f298870b4afe943", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4e616c4976a8cc24c20fda3c6bfcde4cfa22483f" +}] diff --git a/test/corpus/diff-summaries/javascript/regex.json b/test/corpus/diff-summaries/javascript/regex.json new file mode 100644 index 000000000..15ecde5db --- /dev/null +++ b/test/corpus/diff-summaries/javascript/regex.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-regex-insert-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the '/one/g' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "87a75eabc61b58f15583babf507419181ab63aeb", + "gitDir": "test/corpus/repos/javascript", + "sha2": "650dad8817cc6e81699795ce01d6f55f47ee8467" +} +,{ + "testCaseDescription": "javascript-regex-replacement-insert-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 15 + ] + } + }, + "summary": "Added the '/on[^/]afe/gim' regex", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "regex.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the '/one/g' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "650dad8817cc6e81699795ce01d6f55f47ee8467", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6ccce2bf1a0492d851f6a12566b7eecabbc53e7c" +} +,{ + "testCaseDescription": "javascript-regex-delete-insert-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 15 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the '/on[^/]afe/gim' regex with the '/one/g' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "6ccce2bf1a0492d851f6a12566b7eecabbc53e7c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "20edafc45d28234ef35c2f4ac6c5f3b72a9e178a" +} +,{ + "testCaseDescription": "javascript-regex-replacement-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 15 + ] + } + ] + }, + "summary": "Replaced the '/one/g' regex with the '/on[^/]afe/gim' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "20edafc45d28234ef35c2f4ac6c5f3b72a9e178a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3f6396c441334c8beaa3819e7b6cdb44196341c3" +} +,{ + "testCaseDescription": "javascript-regex-delete-replacement-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 15 + ] + } + }, + "summary": "Deleted the '/on[^/]afe/gim' regex", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "regex.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Deleted the '/one/g' regex", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "regex.js", + "end": [ + 2, + 15 + ] + } + }, + "summary": "Added the '/on[^/]afe/gim' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "3f6396c441334c8beaa3819e7b6cdb44196341c3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a09af80adb555a0c9c30839fbe7014942bfcf449" +} +,{ + "testCaseDescription": "javascript-regex-delete-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the '/one/g' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "a09af80adb555a0c9c30839fbe7014942bfcf449", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e0e94d4e600134f55d47ad0fbdea6f791be2e618" +} +,{ + "testCaseDescription": "javascript-regex-delete-rest-test", + "expectedResult": { + "changes": { + "regex.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "regex.js", + "end": [ + 1, + 15 + ] + } + }, + "summary": "Deleted the '/on[^/]afe/gim' regex", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "regex.js" + ], + "sha1": "e0e94d4e600134f55d47ad0fbdea6f791be2e618", + "gitDir": "test/corpus/repos/javascript", + "sha2": "408411b4e79d51cf3b50541c8d1115a3ce46dfa8" +}] diff --git a/test/corpus/diff-summaries/javascript/relational-operator.json b/test/corpus/diff-summaries/javascript/relational-operator.json new file mode 100644 index 000000000..d5057eed0 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/relational-operator.json @@ -0,0 +1,208 @@ +[{ + "testCaseDescription": "javascript-relational-operator-insert-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "relational-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'x < y' relational operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "8cdb0cc77bfe88b76c86dcde66d08f97f11182f3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "da2638f6fc96de8b58f104e1db1d5a665b5e3a9b" +} +,{ + "testCaseDescription": "javascript-relational-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "relational-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'x <= y' relational operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "relational-operator.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added the 'x < y' relational operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "da2638f6fc96de8b58f104e1db1d5a665b5e3a9b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "95ef181dcd3fc26ed54bf60bfd60447a51c8ffd7" +} +,{ + "testCaseDescription": "javascript-relational-operator-delete-insert-test", + "expectedResult": { + "changes": {}, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "95ef181dcd3fc26ed54bf60bfd60447a51c8ffd7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d3346f7942edffe06e10ca06433091c89a815a74" +} +,{ + "testCaseDescription": "javascript-relational-operator-replacement-test", + "expectedResult": { + "changes": {}, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "d3346f7942edffe06e10ca06433091c89a815a74", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8b110a7eeb3d75ad831ec61d91539bb3110a5c82" +} +,{ + "testCaseDescription": "javascript-relational-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "relational-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'x <= y' relational operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "8b110a7eeb3d75ad831ec61d91539bb3110a5c82", + "gitDir": "test/corpus/repos/javascript", + "sha2": "02d3364197afdd61f67f2e693ae3a8d09c64560f" +} +,{ + "testCaseDescription": "javascript-relational-operator-delete-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "relational-operator.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x < y' relational operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "02d3364197afdd61f67f2e693ae3a8d09c64560f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "59255aa8bf840f1bf5dc446a5c4190a538be2f13" +} +,{ + "testCaseDescription": "javascript-relational-operator-delete-rest-test", + "expectedResult": { + "changes": { + "relational-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "relational-operator.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'x <= y' relational operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "relational-operator.js" + ], + "sha1": "59255aa8bf840f1bf5dc446a5c4190a538be2f13", + "gitDir": "test/corpus/repos/javascript", + "sha2": "761990749004312c4b5e474eeacb839376523f0b" +}] diff --git a/test/corpus/diff-summaries/javascript/return-statement.json b/test/corpus/diff-summaries/javascript/return-statement.json new file mode 100644 index 000000000..732bbe3f3 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/return-statement.json @@ -0,0 +1,282 @@ +[{ + "testCaseDescription": "javascript-return-statement-insert-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "return-statement.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Added the '5' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "a6c49cc7711970d9b1fdcfeef8ea1b312bcf0ace", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cce29acfef026dd830249e9d1336513f6e3c4304" +} +,{ + "testCaseDescription": "javascript-return-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "return-statement.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Added the 'empty' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "return-statement.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Added the '5' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "cce29acfef026dd830249e9d1336513f6e3c4304", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c8de458d3d17e648dfbf1869bb0b1ce2e0979601" +} +,{ + "testCaseDescription": "javascript-return-statement-delete-insert-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 8 + ], + "name": "return-statement.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Added '5'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "c8de458d3d17e648dfbf1869bb0b1ce2e0979601", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1ec1da945159b2908ed73826fa61ed65680b7ab0" +} +,{ + "testCaseDescription": "javascript-return-statement-replacement-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "return-statement.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Deleted '5'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "1ec1da945159b2908ed73826fa61ed65680b7ab0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d942adb626ca42c2407c698701c173fcf1215775" +} +,{ + "testCaseDescription": "javascript-return-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "return-statement.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'empty' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "return-statement.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Deleted the '5' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "return-statement.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Added the 'empty' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "d942adb626ca42c2407c698701c173fcf1215775", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d4af520a89d43ed45e2ab60753d6b5e0542c2812" +} +,{ + "testCaseDescription": "javascript-return-statement-delete-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "return-statement.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Deleted the '5' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "d4af520a89d43ed45e2ab60753d6b5e0542c2812", + "gitDir": "test/corpus/repos/javascript", + "sha2": "006d0dd9f64dfec01d6a4027448f81864951fc14" +} +,{ + "testCaseDescription": "javascript-return-statement-delete-rest-test", + "expectedResult": { + "changes": { + "return-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "return-statement.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'empty' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "return-statement.js" + ], + "sha1": "006d0dd9f64dfec01d6a4027448f81864951fc14", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a5fb0a1bf511cc98cae35a20ea3a6dad064448bc" +}] diff --git a/test/corpus/diff-summaries/javascript/string.json b/test/corpus/diff-summaries/javascript/string.json new file mode 100644 index 000000000..76fc97c66 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/string.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-string-insert-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Added the 'A string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "71a215c337687c245da7c6eafcba311e3ba0e09b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "890f6940b147be1142451548897bb522f2cc0e0e" +} +,{ + "testCaseDescription": "javascript-string-replacement-insert-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Added the 'A different string with \"double\" quotes' string", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "string.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Added the 'A string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "890f6940b147be1142451548897bb522f2cc0e0e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a1bd8ab3294f256b512c1c8f2e71e36f5382c5dc" +} +,{ + "testCaseDescription": "javascript-string-delete-insert-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 42 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 32 + ] + } + ] + }, + "summary": "Replaced the 'A different string with \"double\" quotes' string with the 'A string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "a1bd8ab3294f256b512c1c8f2e71e36f5382c5dc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6965b973b84c4170ec98730272475e697686d29e" +} +,{ + "testCaseDescription": "javascript-string-replacement-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 32 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 42 + ] + } + ] + }, + "summary": "Replaced the 'A string with \"double\" quotes' string with the 'A different string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "6965b973b84c4170ec98730272475e697686d29e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "92a860f5c70f4aa4da65a6919a026b01d717804c" +} +,{ + "testCaseDescription": "javascript-string-delete-replacement-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'A different string with \"double\" quotes' string", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "string.js", + "end": [ + 2, + 32 + ] + } + }, + "summary": "Deleted the 'A string with \"double\" quotes' string", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "string.js", + "end": [ + 2, + 42 + ] + } + }, + "summary": "Added the 'A different string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "92a860f5c70f4aa4da65a6919a026b01d717804c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "27d40a59d34bcf26ccd02b06f857c20f85a9df41" +} +,{ + "testCaseDescription": "javascript-string-delete-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 32 + ] + } + }, + "summary": "Deleted the 'A string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "27d40a59d34bcf26ccd02b06f857c20f85a9df41", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b18bf04fd766cc584977cd2ba38b84199ab2f62d" +} +,{ + "testCaseDescription": "javascript-string-delete-rest-test", + "expectedResult": { + "changes": { + "string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "string.js", + "end": [ + 1, + 42 + ] + } + }, + "summary": "Deleted the 'A different string with \"double\" quotes' string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "string.js" + ], + "sha1": "b18bf04fd766cc584977cd2ba38b84199ab2f62d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6353fa1218bad4624b606cf46bfcd6c18d1e13c2" +}] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-assignment.json b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json new file mode 100644 index 000000000..277f48e77 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/subscript-access-assignment.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-subscript-access-assignment-insert-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Added the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "0286a0f0ca80520eb670a372dbf844ec8357639e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8303b810d953c09eec10797a00b3ab66d923e510" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Added the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 2, + 11 + ] + } + }, + "summary": "Added the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "8303b810d953c09eec10797a00b3ab66d923e510", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3db24d6ecd3ac85657b5c13192208dbc4a86a6bf" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced '1' with '0' in an assignment to y[\"x\"]", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "3db24d6ecd3ac85657b5c13192208dbc4a86a6bf", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3a74a00c6e3ef58372e16138057561bbdaaa9e09" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 10 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 10 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced '0' with '1' in an assignment to y[\"x\"]", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "3a74a00c6e3ef58372e16138057561bbdaaa9e09", + "gitDir": "test/corpus/repos/javascript", + "sha2": "59489169d3ee84ebaebab0a32db21de5feda9b9b" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Deleted the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 2, + 11 + ] + } + }, + "summary": "Deleted the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 2, + 11 + ] + } + }, + "summary": "Added the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "59489169d3ee84ebaebab0a32db21de5feda9b9b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "37120ecde944db661969f1cedbda2aa0796858eb" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-delete-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Deleted the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "37120ecde944db661969f1cedbda2aa0796858eb", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8632cbda9073b25b4a495c242641b1eb01d4a260" +} +,{ + "testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test", + "expectedResult": { + "changes": { + "subscript-access-assignment.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-assignment.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Deleted the 'y[\"x\"]' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-assignment.js" + ], + "sha1": "8632cbda9073b25b4a495c242641b1eb01d4a260", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ea966e7428b15b541246b765517db3f0ef1c6af8" +}] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-string.json b/test/corpus/diff-summaries/javascript/subscript-access-string.json new file mode 100644 index 000000000..f8120c282 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/subscript-access-string.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-subscript-access-string-insert-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Added the 'x[\"some-string\"]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "b5a7a5a17e38194441efeaf2ddc572cf612a050c", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ab035d165637ae2f6549f91b23cb3d8397086a5b" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-replacement-insert-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Added the 'x[\"some-other-string\"]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 2, + 17 + ] + } + }, + "summary": "Added the 'x[\"some-string\"]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "ab035d165637ae2f6549f91b23cb3d8397086a5b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6a0dd5ec60be73dd88995bbf2fc987895204fd69" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-delete-insert-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 22 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 16 + ] + } + ] + }, + "summary": "Replaced the \"some-other-string\" string with the \"some-string\" string in the x[\"some-string\"] subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "6a0dd5ec60be73dd88995bbf2fc987895204fd69", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cf1ef60479b2d9c834590a4c6f4f7717a657e1cd" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 16 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 22 + ] + } + ] + }, + "summary": "Replaced the \"some-string\" string with the \"some-other-string\" string in the x[\"some-other-string\"] subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "cf1ef60479b2d9c834590a4c6f4f7717a657e1cd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c476a25c1998c3c480523c8179b29584ad2e00a3" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-delete-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Deleted the 'x[\"some-other-string\"]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 2, + 17 + ] + } + }, + "summary": "Deleted the 'x[\"some-string\"]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 2, + 23 + ] + } + }, + "summary": "Added the 'x[\"some-other-string\"]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "c476a25c1998c3c480523c8179b29584ad2e00a3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2f049bd94a6e832b099c647e31ee0a028fa26051" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-delete-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Deleted the 'x[\"some-string\"]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "2f049bd94a6e832b099c647e31ee0a028fa26051", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a88fd09203e1ffb45ef9d0b5a916150099d2f0d7" +} +,{ + "testCaseDescription": "javascript-subscript-access-string-delete-rest-test", + "expectedResult": { + "changes": { + "subscript-access-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-string.js", + "end": [ + 1, + 23 + ] + } + }, + "summary": "Deleted the 'x[\"some-other-string\"]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-string.js" + ], + "sha1": "a88fd09203e1ffb45ef9d0b5a916150099d2f0d7", + "gitDir": "test/corpus/repos/javascript", + "sha2": "07c5dd47cd837cd06d7d034c049ea6002a5e0980" +}] diff --git a/test/corpus/diff-summaries/javascript/subscript-access-variable.json b/test/corpus/diff-summaries/javascript/subscript-access-variable.json new file mode 100644 index 000000000..3140c1e63 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/subscript-access-variable.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-subscript-access-variable-insert-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 16 + ] + } + }, + "summary": "Added the 'x[someVariable]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "c77d21ce31ff19818614b186e90aa577cc20ce9d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4d5dda84d5715cb19e8562fa86ec775ad7bc3b52" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Added the 'x[someOtherVariable]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 2, + 16 + ] + } + }, + "summary": "Added the 'x[someVariable]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "4d5dda84d5715cb19e8562fa86ec775ad7bc3b52", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a73be8ec6fa12c27b78977f88cde47c3131f85a0" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-delete-insert-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 20 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 15 + ] + } + ] + }, + "summary": "Replaced the 'someOtherVariable' identifier with the 'someVariable' identifier in the x[someVariable] subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "a73be8ec6fa12c27b78977f88cde47c3131f85a0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b1f52c7fa0096992d231a1a96f2d3c6bd350a948" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 15 + ] + }, + { + "start": [ + 1, + 3 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 20 + ] + } + ] + }, + "summary": "Replaced the 'someVariable' identifier with the 'someOtherVariable' identifier in the x[someOtherVariable] subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "b1f52c7fa0096992d231a1a96f2d3c6bd350a948", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d7d36537db64ed980915c9fd7438eb28aca9121a" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the 'x[someOtherVariable]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 2, + 16 + ] + } + }, + "summary": "Deleted the 'x[someVariable]' subscript access", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 2, + 21 + ] + } + }, + "summary": "Added the 'x[someOtherVariable]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "d7d36537db64ed980915c9fd7438eb28aca9121a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "39e4553a4dc76006a19f6907144fe12affe9b3bf" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-delete-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 16 + ] + } + }, + "summary": "Deleted the 'x[someVariable]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "39e4553a4dc76006a19f6907144fe12affe9b3bf", + "gitDir": "test/corpus/repos/javascript", + "sha2": "579578d94e6d3639fef8ef66a5c71d990e4f7a95" +} +,{ + "testCaseDescription": "javascript-subscript-access-variable-delete-rest-test", + "expectedResult": { + "changes": { + "subscript-access-variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "subscript-access-variable.js", + "end": [ + 1, + 21 + ] + } + }, + "summary": "Deleted the 'x[someOtherVariable]' subscript access", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "subscript-access-variable.js" + ], + "sha1": "579578d94e6d3639fef8ef66a5c71d990e4f7a95", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b5a7a5a17e38194441efeaf2ddc572cf612a050c" +}] diff --git a/test/corpus/diff-summaries/javascript/switch-statement.json b/test/corpus/diff-summaries/javascript/switch-statement.json new file mode 100644 index 000000000..c070de7a0 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/switch-statement.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-switch-statement-insert-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "switch-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Added the '1' switch statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "df276ed5f435d4cf1363008ae573ea99ba39e175", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e906cd9ad5ab469f68df1fd23910bbe78a9f8cd1" +} +,{ + "testCaseDescription": "javascript-switch-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "switch-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Added the '2' switch statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "switch-statement.js", + "end": [ + 2, + 48 + ] + } + }, + "summary": "Added the '1' switch statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "e906cd9ad5ab469f68df1fd23910bbe78a9f8cd1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b5602de388c92c96c7f62e0fcf1cce07b403c185" +} +,{ + "testCaseDescription": "javascript-switch-statement-delete-insert-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 9 + ], + "name": "switch-statement.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 9 + ], + "name": "switch-statement.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced '2' with '1'", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 33 + ], + "name": "switch-statement.js", + "end": [ + 1, + 34 + ] + }, + { + "start": [ + 1, + 33 + ], + "name": "switch-statement.js", + "end": [ + 1, + 34 + ] + } + ] + }, + "summary": "Replaced '2' with '1'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "b5602de388c92c96c7f62e0fcf1cce07b403c185", + "gitDir": "test/corpus/repos/javascript", + "sha2": "fa74d55721267c11d2be5de262e9eb3100ba91f0" +} +,{ + "testCaseDescription": "javascript-switch-statement-replacement-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 9 + ], + "name": "switch-statement.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 9 + ], + "name": "switch-statement.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced '1' with '2'", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 33 + ], + "name": "switch-statement.js", + "end": [ + 1, + 34 + ] + }, + { + "start": [ + 1, + 33 + ], + "name": "switch-statement.js", + "end": [ + 1, + 34 + ] + } + ] + }, + "summary": "Replaced '1' with '2'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "fa74d55721267c11d2be5de262e9eb3100ba91f0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "14d176ab7a67005a68ef8e96781993f1e9e8aff0" +} +,{ + "testCaseDescription": "javascript-switch-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "switch-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Deleted the '2' switch statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "switch-statement.js", + "end": [ + 2, + 48 + ] + } + }, + "summary": "Deleted the '1' switch statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "switch-statement.js", + "end": [ + 2, + 48 + ] + } + }, + "summary": "Added the '2' switch statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "14d176ab7a67005a68ef8e96781993f1e9e8aff0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f3c50550c25a6a350e336bcb4acb19efaee5784b" +} +,{ + "testCaseDescription": "javascript-switch-statement-delete-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "switch-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Deleted the '1' switch statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "f3c50550c25a6a350e336bcb4acb19efaee5784b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "43e7f35abe631d346d4a6d0b20df2215a9844b2a" +} +,{ + "testCaseDescription": "javascript-switch-statement-delete-rest-test", + "expectedResult": { + "changes": { + "switch-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "switch-statement.js", + "end": [ + 1, + 48 + ] + } + }, + "summary": "Deleted the '2' switch statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "switch-statement.js" + ], + "sha1": "43e7f35abe631d346d4a6d0b20df2215a9844b2a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ef9e2caec95767f4944840fd5db7f43806b65d4e" +}] diff --git a/test/corpus/diff-summaries/javascript/template-string.json b/test/corpus/diff-summaries/javascript/template-string.json new file mode 100644 index 000000000..a1010f774 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/template-string.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-template-string-insert-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Added the '`one line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "125f2e2e8e65a10784e72bb113319c805d4f42ac", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a3356557da2051db1550e86d98e0125c04a76786" +} +,{ + "testCaseDescription": "javascript-template-string-replacement-insert-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the '`multi line`' template string", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "template-string.js", + "end": [ + 2, + 11 + ] + } + }, + "summary": "Added the '`one line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "a3356557da2051db1550e86d98e0125c04a76786", + "gitDir": "test/corpus/repos/javascript", + "sha2": "90c33afc22831d46016cae3ef48184f5181a3209" +} +,{ + "testCaseDescription": "javascript-template-string-delete-insert-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 13 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 11 + ] + } + ] + }, + "summary": "Replaced the '`multi line`' template string with the '`one line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "90c33afc22831d46016cae3ef48184f5181a3209", + "gitDir": "test/corpus/repos/javascript", + "sha2": "41c65d10f9fd1e98f553137da5ac3ec04a6e816a" +} +,{ + "testCaseDescription": "javascript-template-string-replacement-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 11 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 13 + ] + } + ] + }, + "summary": "Replaced the '`one line`' template string with the '`multi line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "41c65d10f9fd1e98f553137da5ac3ec04a6e816a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1f70c585f7fd042fbc6d4318040f4cf1346a8f6d" +} +,{ + "testCaseDescription": "javascript-template-string-delete-replacement-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the '`multi line`' template string", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "template-string.js", + "end": [ + 2, + 11 + ] + } + }, + "summary": "Deleted the '`one line`' template string", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "template-string.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Added the '`multi line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "1f70c585f7fd042fbc6d4318040f4cf1346a8f6d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "53609feaa56d71f8929c26bf0653e4559ed8baa4" +} +,{ + "testCaseDescription": "javascript-template-string-delete-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 11 + ] + } + }, + "summary": "Deleted the '`one line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "53609feaa56d71f8929c26bf0653e4559ed8baa4", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bc277e6624d14eb866c65fb7668dcd6a678b9eaa" +} +,{ + "testCaseDescription": "javascript-template-string-delete-rest-test", + "expectedResult": { + "changes": { + "template-string.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "template-string.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the '`multi line`' template string", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "bc277e6624d14eb866c65fb7668dcd6a678b9eaa", + "gitDir": "test/corpus/repos/javascript", + "sha2": "2017d7a8b91c62e06d4de3654b0a7a2d550e55b9" +}] diff --git a/test/corpus/diff-summaries/javascript/ternary.json b/test/corpus/diff-summaries/javascript/ternary.json new file mode 100644 index 000000000..97efc7f09 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/ternary.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-ternary-insert-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Added the 'condition' ternary expression", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "7d593b800284097a4d4f70fe25aebef1cbbe69c3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "df07d4313d01aaa48070484b81a515d4b38e229b" +} +,{ + "testCaseDescription": "javascript-ternary-replacement-insert-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 51 + ] + } + }, + "summary": "Added the 'x.y' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "ternary.js", + "end": [ + 2, + 26 + ] + } + }, + "summary": "Added the 'condition' ternary expression", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "df07d4313d01aaa48070484b81a515d4b38e229b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d816f96bfa4a4e3f7d2fed8a1873e45aba4793cb" +} +,{ + "testCaseDescription": "javascript-ternary-delete-insert-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Added the 'condition' ternary expression", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 51 + ] + } + }, + "summary": "Deleted the 'x.y' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "d816f96bfa4a4e3f7d2fed8a1873e45aba4793cb", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7a965762c520641e9bed35cf4f64a0d7aa2caf9d" +} +,{ + "testCaseDescription": "javascript-ternary-replacement-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 51 + ] + } + }, + "summary": "Added the 'x.y' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Deleted the 'condition' ternary expression", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "7a965762c520641e9bed35cf4f64a0d7aa2caf9d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d5904189993b67d55a85720cfe76815ef2861496" +} +,{ + "testCaseDescription": "javascript-ternary-delete-replacement-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 51 + ] + } + }, + "summary": "Deleted the 'x.y' assignment", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "ternary.js", + "end": [ + 2, + 26 + ] + } + }, + "summary": "Deleted the 'condition' ternary expression", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "ternary.js", + "end": [ + 2, + 51 + ] + } + }, + "summary": "Added the 'x.y' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "d5904189993b67d55a85720cfe76815ef2861496", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e7d084239ead8cbe5eb51443a181c7d43f0458aa" +} +,{ + "testCaseDescription": "javascript-ternary-delete-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Deleted the 'condition' ternary expression", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "e7d084239ead8cbe5eb51443a181c7d43f0458aa", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6feb3f80562f534aaef7a5c3814f69c8b509b487" +} +,{ + "testCaseDescription": "javascript-ternary-delete-rest-test", + "expectedResult": { + "changes": { + "ternary.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "ternary.js", + "end": [ + 1, + 51 + ] + } + }, + "summary": "Deleted the 'x.y' assignment", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "ternary.js" + ], + "sha1": "6feb3f80562f534aaef7a5c3814f69c8b509b487", + "gitDir": "test/corpus/repos/javascript", + "sha2": "10e446483f5cfbc3b6a595cf22bcd8e5b4b7fa1f" +}] diff --git a/test/corpus/diff-summaries/javascript/this-expression.json b/test/corpus/diff-summaries/javascript/this-expression.json new file mode 100644 index 000000000..f26e86f5b --- /dev/null +++ b/test/corpus/diff-summaries/javascript/this-expression.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-this-expression-insert-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added the 'this' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "ebab90bd29d724f6dda4d39a32a6fa7d0b9adf52", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e28cc543f4228740ad7e5b4680afb8cbf9c51243" +} +,{ + "testCaseDescription": "javascript-this-expression-replacement-insert-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'this' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "this-expression.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Added the 'this' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "e28cc543f4228740ad7e5b4680afb8cbf9c51243", + "gitDir": "test/corpus/repos/javascript", + "sha2": "552578420a183fd55293708a7cc2b243ca1d657e" +} +,{ + "testCaseDescription": "javascript-this-expression-delete-insert-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added the 'this' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'this' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "552578420a183fd55293708a7cc2b243ca1d657e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "39b0ac559626f4dc67b1e083a93a785c50ba88f6" +} +,{ + "testCaseDescription": "javascript-this-expression-replacement-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'this' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted the 'this' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "39b0ac559626f4dc67b1e083a93a785c50ba88f6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1792d3469977ef42255a501612f9ab858d918c65" +} +,{ + "testCaseDescription": "javascript-this-expression-delete-replacement-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'this' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "this-expression.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Deleted the 'this' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "this-expression.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Added the 'this' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "1792d3469977ef42255a501612f9ab858d918c65", + "gitDir": "test/corpus/repos/javascript", + "sha2": "1153598d3f6368a7cada09f10d73306a6e6857a3" +} +,{ + "testCaseDescription": "javascript-this-expression-delete-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted the 'this' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "1153598d3f6368a7cada09f10d73306a6e6857a3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d2ae1e6938e47ab5b41d0eb89fb0cd1087445e06" +} +,{ + "testCaseDescription": "javascript-this-expression-delete-rest-test", + "expectedResult": { + "changes": { + "this-expression.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "this-expression.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'this' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "this-expression.js" + ], + "sha1": "d2ae1e6938e47ab5b41d0eb89fb0cd1087445e06", + "gitDir": "test/corpus/repos/javascript", + "sha2": "11a27a81f8e7e33aac2eb0844d3465acf8f9bb0d" +}] diff --git a/test/corpus/diff-summaries/javascript/throw-statement.json b/test/corpus/diff-summaries/javascript/throw-statement.json new file mode 100644 index 000000000..7dcc88d6d --- /dev/null +++ b/test/corpus/diff-summaries/javascript/throw-statement.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-throw-statement-insert-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "throw-statement.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Added the 'new Error(\"uh oh\")' throw statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "ef9e2caec95767f4944840fd5db7f43806b65d4e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e8ffd161fc105086e8c085de252fd15f1582df33" +} +,{ + "testCaseDescription": "javascript-throw-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "throw-statement.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Added the 'new Error(\"oooooops\")' throw statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "throw-statement.js", + "end": [ + 2, + 26 + ] + } + }, + "summary": "Added the 'new Error(\"uh oh\")' throw statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "e8ffd161fc105086e8c085de252fd15f1582df33", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0ff2edba17e3040f87a6685ed6ea554a4f520254" +} +,{ + "testCaseDescription": "javascript-throw-statement-delete-insert-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "throw-statement.js", + "end": [ + 1, + 27 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "throw-statement.js", + "end": [ + 1, + 24 + ] + } + ] + }, + "summary": "Replaced the \"oooooops\" string with the \"uh oh\" string in the Error(\"uh oh\") function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "0ff2edba17e3040f87a6685ed6ea554a4f520254", + "gitDir": "test/corpus/repos/javascript", + "sha2": "911f32d28e0aa19e34646b9917cdcf6eb51b16f0" +} +,{ + "testCaseDescription": "javascript-throw-statement-replacement-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 17 + ], + "name": "throw-statement.js", + "end": [ + 1, + 24 + ] + }, + { + "start": [ + 1, + 17 + ], + "name": "throw-statement.js", + "end": [ + 1, + 27 + ] + } + ] + }, + "summary": "Replaced the \"uh oh\" string with the \"oooooops\" string in the Error(\"oooooops\") function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "911f32d28e0aa19e34646b9917cdcf6eb51b16f0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "441deaae5ebff81f6802d5e2f9f4ae276db41c3b" +} +,{ + "testCaseDescription": "javascript-throw-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "throw-statement.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'new Error(\"oooooops\")' throw statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "throw-statement.js", + "end": [ + 2, + 26 + ] + } + }, + "summary": "Deleted the 'new Error(\"uh oh\")' throw statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "throw-statement.js", + "end": [ + 2, + 29 + ] + } + }, + "summary": "Added the 'new Error(\"oooooops\")' throw statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "441deaae5ebff81f6802d5e2f9f4ae276db41c3b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "753074bc4ed4fbcc549b57307a13bc068a4dc0ff" +} +,{ + "testCaseDescription": "javascript-throw-statement-delete-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "throw-statement.js", + "end": [ + 1, + 26 + ] + } + }, + "summary": "Deleted the 'new Error(\"uh oh\")' throw statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "753074bc4ed4fbcc549b57307a13bc068a4dc0ff", + "gitDir": "test/corpus/repos/javascript", + "sha2": "41cdf55b68dce5bdc74df0f541995f9603d2014d" +} +,{ + "testCaseDescription": "javascript-throw-statement-delete-rest-test", + "expectedResult": { + "changes": { + "throw-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "throw-statement.js", + "end": [ + 1, + 29 + ] + } + }, + "summary": "Deleted the 'new Error(\"oooooops\")' throw statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "throw-statement.js" + ], + "sha1": "41cdf55b68dce5bdc74df0f541995f9603d2014d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8853e12eb348f42061f28c7a65748dd8c2b6cdda" +}] diff --git a/test/corpus/diff-summaries/javascript/true.json b/test/corpus/diff-summaries/javascript/true.json new file mode 100644 index 000000000..4a82be170 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/true.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-true-insert-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added 'true'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "c40f78d8ec9a8873d55c8d368978e674c1dfc2d8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "656b27635a5debd119ebc672643c188946ff6963" +} +,{ + "testCaseDescription": "javascript-true-replacement-insert-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'true' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "true.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Added 'true'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "656b27635a5debd119ebc672643c188946ff6963", + "gitDir": "test/corpus/repos/javascript", + "sha2": "63973077f6a477896c7a929a14079bf4bbaadb30" +} +,{ + "testCaseDescription": "javascript-true-delete-insert-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Added 'true'", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'true' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "63973077f6a477896c7a929a14079bf4bbaadb30", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3853f8cb4f7f378206fafa6409d03a2630a15f1a" +} +,{ + "testCaseDescription": "javascript-true-replacement-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Added the 'true' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted 'true'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "3853f8cb4f7f378206fafa6409d03a2630a15f1a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e19548511ad78553ec47f28afe71c1b05d3cefb0" +} +,{ + "testCaseDescription": "javascript-true-delete-replacement-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'true' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "true.js", + "end": [ + 2, + 5 + ] + } + }, + "summary": "Deleted 'true'", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "true.js", + "end": [ + 2, + 13 + ] + } + }, + "summary": "Added the 'true' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "e19548511ad78553ec47f28afe71c1b05d3cefb0", + "gitDir": "test/corpus/repos/javascript", + "sha2": "551e03fb9cd6912f8f1fa0672eaa64c3c6568bd9" +} +,{ + "testCaseDescription": "javascript-true-delete-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 5 + ] + } + }, + "summary": "Deleted 'true'", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "551e03fb9cd6912f8f1fa0672eaa64c3c6568bd9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "77cbe0371de746912cba103518368ac85987da73" +} +,{ + "testCaseDescription": "javascript-true-delete-rest-test", + "expectedResult": { + "changes": { + "true.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "true.js", + "end": [ + 1, + 13 + ] + } + }, + "summary": "Deleted the 'true' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "true.js" + ], + "sha1": "77cbe0371de746912cba103518368ac85987da73", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d1241fa4218f33189f78a91a9513ca7e2120a2a0" +}] diff --git a/test/corpus/diff-summaries/javascript/try-statement.json b/test/corpus/diff-summaries/javascript/try-statement.json new file mode 100644 index 000000000..b8ce833ea --- /dev/null +++ b/test/corpus/diff-summaries/javascript/try-statement.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-try-statement-insert-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "try-statement.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Added the '{ f; }' try statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "8853e12eb348f42061f28c7a65748dd8c2b6cdda", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9a940b48df9acd8141dce91926326bb545a35ce9" +} +,{ + "testCaseDescription": "javascript-try-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "try-statement.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Added the '{ f; }' try statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "try-statement.js", + "end": [ + 2, + 39 + ] + } + }, + "summary": "Added the '{ f; }' try statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "9a940b48df9acd8141dce91926326bb545a35ce9", + "gitDir": "test/corpus/repos/javascript", + "sha2": "14485b720f542fc02c659aeb388d28a4f23d5eca" +} +,{ + "testCaseDescription": "javascript-try-statement-delete-insert-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "try-statement.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "try-statement.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'h' identifier with the 'g' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 35 + ], + "name": "try-statement.js", + "end": [ + 1, + 36 + ] + }, + { + "start": [ + 1, + 35 + ], + "name": "try-statement.js", + "end": [ + 1, + 36 + ] + } + ] + }, + "summary": "Replaced the 'g' identifier with the 'h' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "14485b720f542fc02c659aeb388d28a4f23d5eca", + "gitDir": "test/corpus/repos/javascript", + "sha2": "937bc39ba6b5a8ea39d5e70a05aca172340b34b8" +} +,{ + "testCaseDescription": "javascript-try-statement-replacement-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 20 + ], + "name": "try-statement.js", + "end": [ + 1, + 21 + ] + }, + { + "start": [ + 1, + 20 + ], + "name": "try-statement.js", + "end": [ + 1, + 21 + ] + } + ] + }, + "summary": "Replaced the 'g' identifier with the 'h' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 35 + ], + "name": "try-statement.js", + "end": [ + 1, + 36 + ] + }, + { + "start": [ + 1, + 35 + ], + "name": "try-statement.js", + "end": [ + 1, + 36 + ] + } + ] + }, + "summary": "Replaced the 'h' identifier with the 'g' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "937bc39ba6b5a8ea39d5e70a05aca172340b34b8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d5388b993d81d166c72a2c0851cadf209a53e663" +} +,{ + "testCaseDescription": "javascript-try-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "try-statement.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Deleted the '{ f; }' try statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "try-statement.js", + "end": [ + 2, + 39 + ] + } + }, + "summary": "Deleted the '{ f; }' try statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "try-statement.js", + "end": [ + 2, + 39 + ] + } + }, + "summary": "Added the '{ f; }' try statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "d5388b993d81d166c72a2c0851cadf209a53e663", + "gitDir": "test/corpus/repos/javascript", + "sha2": "dcc5fa3d3acd27cfef2eab524cd619a2518e375f" +} +,{ + "testCaseDescription": "javascript-try-statement-delete-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "try-statement.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Deleted the '{ f; }' try statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "dcc5fa3d3acd27cfef2eab524cd619a2518e375f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4f2e99ffade0f4b59764c6dc000ea251ffd1876b" +} +,{ + "testCaseDescription": "javascript-try-statement-delete-rest-test", + "expectedResult": { + "changes": { + "try-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "try-statement.js", + "end": [ + 1, + 39 + ] + } + }, + "summary": "Deleted the '{ f; }' try statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "try-statement.js" + ], + "sha1": "4f2e99ffade0f4b59764c6dc000ea251ffd1876b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "87a75eabc61b58f15583babf507419181ab63aeb" +}] diff --git a/test/corpus/diff-summaries/javascript/type-operator.json b/test/corpus/diff-summaries/javascript/type-operator.json new file mode 100644 index 000000000..33fe2faf5 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/type-operator.json @@ -0,0 +1,282 @@ +[{ + "testCaseDescription": "javascript-type-operator-insert-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "type-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Added the 'typeof x' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "10e446483f5cfbc3b6a595cf22bcd8e5b4b7fa1f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e824baf85c2455f92ee90fc9344ac39d72a50a14" +} +,{ + "testCaseDescription": "javascript-type-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "type-operator.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Added the 'x instanceof String' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "type-operator.js", + "end": [ + 2, + 9 + ] + } + }, + "summary": "Added the 'typeof x' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "e824baf85c2455f92ee90fc9344ac39d72a50a14", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4c4620dc49de1618fc2688d086a90b0c33b56172" +} +,{ + "testCaseDescription": "javascript-type-operator-delete-insert-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 14 + ], + "name": "type-operator.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Deleted the 'String' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "4c4620dc49de1618fc2688d086a90b0c33b56172", + "gitDir": "test/corpus/repos/javascript", + "sha2": "cb84bfa2a54e105154cc4f64f3edbdec593da924" +} +,{ + "testCaseDescription": "javascript-type-operator-replacement-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 14 + ], + "name": "type-operator.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Added the 'String' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "cb84bfa2a54e105154cc4f64f3edbdec593da924", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3906b75677e7e34461038b42a7d0eed388638d1a" +} +,{ + "testCaseDescription": "javascript-type-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "type-operator.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Deleted the 'x instanceof String' operator", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "type-operator.js", + "end": [ + 2, + 9 + ] + } + }, + "summary": "Deleted the 'typeof x' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "type-operator.js", + "end": [ + 2, + 20 + ] + } + }, + "summary": "Added the 'x instanceof String' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "3906b75677e7e34461038b42a7d0eed388638d1a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "63321c3a8e510775ad5270c30d3f34d4c513363e" +} +,{ + "testCaseDescription": "javascript-type-operator-delete-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "type-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Deleted the 'typeof x' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "63321c3a8e510775ad5270c30d3f34d4c513363e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "553f6f8d42f3dbd74e01e1e8eb376f10010728c5" +} +,{ + "testCaseDescription": "javascript-type-operator-delete-rest-test", + "expectedResult": { + "changes": { + "type-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "type-operator.js", + "end": [ + 1, + 20 + ] + } + }, + "summary": "Deleted the 'x instanceof String' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "type-operator.js" + ], + "sha1": "553f6f8d42f3dbd74e01e1e8eb376f10010728c5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "0014c5d8fc3e6f9d08e268ebbb2d42919d5b4991" +}] diff --git a/test/corpus/diff-summaries/javascript/undefined.json b/test/corpus/diff-summaries/javascript/undefined.json new file mode 100644 index 000000000..3000186bf --- /dev/null +++ b/test/corpus/diff-summaries/javascript/undefined.json @@ -0,0 +1,316 @@ +[{ + "testCaseDescription": "javascript-undefined-insert-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Added the 'undefined' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "43fd131de0f55fa1826e3fa3b95b88b7ba74fd68", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a733439e831bb4ec5f6387c6ff60a2077a1e487d" +} +,{ + "testCaseDescription": "javascript-undefined-replacement-insert-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Added the 'undefined' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "undefined.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Added the 'undefined' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "a733439e831bb4ec5f6387c6ff60a2077a1e487d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9e8bf000f2763e38b7d070a67c4162528edcebcb" +} +,{ + "testCaseDescription": "javascript-undefined-delete-insert-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Added the 'undefined' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'undefined' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "9e8bf000f2763e38b7d070a67c4162528edcebcb", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f5de1863a90afffbf383144a36564fca6c7702ca" +} +,{ + "testCaseDescription": "javascript-undefined-replacement-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Added the 'undefined' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Deleted the 'undefined' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "f5de1863a90afffbf383144a36564fca6c7702ca", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6f6fe3b3395ecaf60ae2e3b9d63f89c332770002" +} +,{ + "testCaseDescription": "javascript-undefined-delete-replacement-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'undefined' return statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "undefined.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Deleted the 'undefined' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "undefined.js", + "end": [ + 2, + 18 + ] + } + }, + "summary": "Added the 'undefined' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "6f6fe3b3395ecaf60ae2e3b9d63f89c332770002", + "gitDir": "test/corpus/repos/javascript", + "sha2": "7c4790c8d32dd788ebf2c2857d39e88250608ea1" +} +,{ + "testCaseDescription": "javascript-undefined-delete-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Deleted the 'undefined' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "7c4790c8d32dd788ebf2c2857d39e88250608ea1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d802c686cf2a1012e7a239acdef816a7eb6b91ae" +} +,{ + "testCaseDescription": "javascript-undefined-delete-rest-test", + "expectedResult": { + "changes": { + "undefined.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "undefined.js", + "end": [ + 1, + 18 + ] + } + }, + "summary": "Deleted the 'undefined' return statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "undefined.js" + ], + "sha1": "d802c686cf2a1012e7a239acdef816a7eb6b91ae", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c40f78d8ec9a8873d55c8d368978e674c1dfc2d8" +}] diff --git a/test/corpus/diff-summaries/javascript/var-declaration.json b/test/corpus/diff-summaries/javascript/var-declaration.json new file mode 100644 index 000000000..e3fcde80b --- /dev/null +++ b/test/corpus/diff-summaries/javascript/var-declaration.json @@ -0,0 +1,512 @@ +[{ + "testCaseDescription": "javascript-var-declaration-insert-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "that": { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Added the 'x' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "a5fb0a1bf511cc98cae35a20ea3a6dad064448bc", + "gitDir": "test/corpus/repos/javascript", + "sha2": "05bb0ae04ba1c8492dbc8091c77e84e7b8fa3706" +} +,{ + "testCaseDescription": "javascript-var-declaration-replacement-insert-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "that": { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Added the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 8 + ], + "name": "var-declaration.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Added the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 16 + ], + "name": "var-declaration.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Added the 'z' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 5 + ], + "name": "var-declaration.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Added the 'x' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "05bb0ae04ba1c8492dbc8091c77e84e7b8fa3706", + "gitDir": "test/corpus/repos/javascript", + "sha2": "390295f402454b7a8a89876ac729014f4c73f6cd" +} +,{ + "testCaseDescription": "javascript-var-declaration-delete-insert-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 6 + ] + }, + { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 10 + ] + } + ] + }, + "summary": "Replaced the 'x' variable with the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "var-declaration.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 16 + ], + "name": "var-declaration.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Deleted the 'z' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "390295f402454b7a8a89876ac729014f4c73f6cd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "ee63d737082c6fcdb3e782d9005591482b25c755" +} +,{ + "testCaseDescription": "javascript-var-declaration-replacement-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 10 + ] + }, + { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 6 + ] + } + ] + }, + "summary": "Replaced the 'x' variable with the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 8 + ], + "name": "var-declaration.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Added the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 1, + 16 + ], + "name": "var-declaration.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Added the 'z' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "ee63d737082c6fcdb3e782d9005591482b25c755", + "gitDir": "test/corpus/repos/javascript", + "sha2": "14ab5aa6580823b08cde9a0d91e674bf712c4896" +} +,{ + "testCaseDescription": "javascript-var-declaration-delete-replacement-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "this": { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "var-declaration.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 16 + ], + "name": "var-declaration.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Deleted the 'z' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 5 + ], + "name": "var-declaration.js", + "end": [ + 2, + 10 + ] + } + }, + "summary": "Deleted the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 5 + ], + "name": "var-declaration.js", + "end": [ + 2, + 6 + ] + } + }, + "summary": "Added the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 8 + ], + "name": "var-declaration.js", + "end": [ + 2, + 14 + ] + } + }, + "summary": "Added the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 16 + ], + "name": "var-declaration.js", + "end": [ + 2, + 17 + ] + } + }, + "summary": "Added the 'z' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "14ab5aa6580823b08cde9a0d91e674bf712c4896", + "gitDir": "test/corpus/repos/javascript", + "sha2": "4949f1ef2caaf01fc368e0fb8010a90a05550c92" +} +,{ + "testCaseDescription": "javascript-var-declaration-delete-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "this": { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 10 + ] + } + }, + "summary": "Deleted the 'x' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "4949f1ef2caaf01fc368e0fb8010a90a05550c92", + "gitDir": "test/corpus/repos/javascript", + "sha2": "bedd174ec888f89deff0be9e6cd87ecf1404c2d5" +} +,{ + "testCaseDescription": "javascript-var-declaration-delete-rest-test", + "expectedResult": { + "changes": { + "var-declaration.js": [ + { + "span": { + "this": { + "start": [ + 1, + 5 + ], + "name": "var-declaration.js", + "end": [ + 1, + 6 + ] + } + }, + "summary": "Deleted the 'x' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 8 + ], + "name": "var-declaration.js", + "end": [ + 1, + 14 + ] + } + }, + "summary": "Deleted the 'y' variable", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 1, + 16 + ], + "name": "var-declaration.js", + "end": [ + 1, + 17 + ] + } + }, + "summary": "Deleted the 'z' variable", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "var-declaration.js" + ], + "sha1": "bedd174ec888f89deff0be9e6cd87ecf1404c2d5", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b00fa825ca435ba80830373e95ab22dd77ce9326" +}] diff --git a/test/corpus/diff-summaries/javascript/variable.json b/test/corpus/diff-summaries/javascript/variable.json new file mode 100644 index 000000000..19f521a62 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/variable.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-variable-insert-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Added the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "7cd0762fb1e84cad3dcf9a1c41b07c8112c888fd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d997c1093fa0c616e4a65bdb9d406275cdd5802d" +} +,{ + "testCaseDescription": "javascript-variable-replacement-insert-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Added the 'theVar2' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "variable.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Added the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "d997c1093fa0c616e4a65bdb9d406275cdd5802d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "d53db14bcba93489810bcd1ac51b4b15306a1ae6" +} +,{ + "testCaseDescription": "javascript-variable-delete-insert-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 8 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "d53db14bcba93489810bcd1ac51b4b15306a1ae6", + "gitDir": "test/corpus/repos/javascript", + "sha2": "3e07fecc10461c1d47c18a19bea04d61a0dfc83a" +} +,{ + "testCaseDescription": "javascript-variable-replacement-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 8 + ] + } + ] + }, + "summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "3e07fecc10461c1d47c18a19bea04d61a0dfc83a", + "gitDir": "test/corpus/repos/javascript", + "sha2": "9a58027ba05317961196f113c79ea9ffad926b20" +} +,{ + "testCaseDescription": "javascript-variable-delete-replacement-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'theVar2' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "variable.js", + "end": [ + 2, + 7 + ] + } + }, + "summary": "Deleted the 'theVar' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "variable.js", + "end": [ + 2, + 8 + ] + } + }, + "summary": "Added the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "9a58027ba05317961196f113c79ea9ffad926b20", + "gitDir": "test/corpus/repos/javascript", + "sha2": "eaebf72a40c5b5efa51afefa013498ddf1954821" +} +,{ + "testCaseDescription": "javascript-variable-delete-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 7 + ] + } + }, + "summary": "Deleted the 'theVar' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "eaebf72a40c5b5efa51afefa013498ddf1954821", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6a047726509cb5ca3ac81e6bff6d14f65205196b" +} +,{ + "testCaseDescription": "javascript-variable-delete-rest-test", + "expectedResult": { + "changes": { + "variable.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "variable.js", + "end": [ + 1, + 8 + ] + } + }, + "summary": "Deleted the 'theVar2' identifier", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "variable.js" + ], + "sha1": "6a047726509cb5ca3ac81e6bff6d14f65205196b", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e117ae3f5e0945e0d8e971f7bbc0397229a45648" +}] diff --git a/test/corpus/diff-summaries/javascript/void-operator.json b/test/corpus/diff-summaries/javascript/void-operator.json new file mode 100644 index 000000000..8f3b4a663 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/void-operator.json @@ -0,0 +1,308 @@ +[{ + "testCaseDescription": "javascript-void-operator-insert-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "void-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Added the 'void b()' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "91bb86f2c473fce6ff1ddd4c4e25a6362131920f", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e235fe3056b7c71256b661b0a336a44da2be1329" +} +,{ + "testCaseDescription": "javascript-void-operator-replacement-insert-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "void-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Added the 'void c()' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "void-operator.js", + "end": [ + 2, + 9 + ] + } + }, + "summary": "Added the 'void b()' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "e235fe3056b7c71256b661b0a336a44da2be1329", + "gitDir": "test/corpus/repos/javascript", + "sha2": "f17f509d54fab1faf744a724bea1e6bc45f88ef1" +} +,{ + "testCaseDescription": "javascript-void-operator-delete-insert-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "void-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "void-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'c' identifier with the 'b' identifier in the b() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "f17f509d54fab1faf744a724bea1e6bc45f88ef1", + "gitDir": "test/corpus/repos/javascript", + "sha2": "27ce188eaba0b82b104b61399b6d52e85c9f2934" +} +,{ + "testCaseDescription": "javascript-void-operator-replacement-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 6 + ], + "name": "void-operator.js", + "end": [ + 1, + 7 + ] + }, + { + "start": [ + 1, + 6 + ], + "name": "void-operator.js", + "end": [ + 1, + 7 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'c' identifier in the c() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "27ce188eaba0b82b104b61399b6d52e85c9f2934", + "gitDir": "test/corpus/repos/javascript", + "sha2": "b88d743bc3413c7955a22108d0b1c5f52b1eedfd" +} +,{ + "testCaseDescription": "javascript-void-operator-delete-replacement-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "void-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Deleted the 'void c()' operator", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "void-operator.js", + "end": [ + 2, + 9 + ] + } + }, + "summary": "Deleted the 'void b()' operator", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "void-operator.js", + "end": [ + 2, + 9 + ] + } + }, + "summary": "Added the 'void c()' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "b88d743bc3413c7955a22108d0b1c5f52b1eedfd", + "gitDir": "test/corpus/repos/javascript", + "sha2": "e77413f973aacde76e8f7b65832eda2e3d83c299" +} +,{ + "testCaseDescription": "javascript-void-operator-delete-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "void-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Deleted the 'void b()' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "e77413f973aacde76e8f7b65832eda2e3d83c299", + "gitDir": "test/corpus/repos/javascript", + "sha2": "57baa35e51004dd414a0bc651d9bb199d393d9a8" +} +,{ + "testCaseDescription": "javascript-void-operator-delete-rest-test", + "expectedResult": { + "changes": { + "void-operator.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "void-operator.js", + "end": [ + 1, + 9 + ] + } + }, + "summary": "Deleted the 'void c()' operator", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "void-operator.js" + ], + "sha1": "57baa35e51004dd414a0bc651d9bb199d393d9a8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "74f192419bb6a3a7ef68bb5eb4cf71e89e09b919" +}] diff --git a/test/corpus/diff-summaries/javascript/while-statement.json b/test/corpus/diff-summaries/javascript/while-statement.json new file mode 100644 index 000000000..d78707ef5 --- /dev/null +++ b/test/corpus/diff-summaries/javascript/while-statement.json @@ -0,0 +1,368 @@ +[{ + "testCaseDescription": "javascript-while-statement-insert-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "while-statement.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Added the 'a' while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "1e95946698829d93a91686c01b91618eb065b077", + "gitDir": "test/corpus/repos/javascript", + "sha2": "003db95c9c468101af6b2a4d74708ad5cfcaeac3" +} +,{ + "testCaseDescription": "javascript-while-statement-replacement-insert-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "that": { + "start": [ + 1, + 1 + ], + "name": "while-statement.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Added the 'b' while statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "while-statement.js", + "end": [ + 2, + 19 + ] + } + }, + "summary": "Added the 'a' while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "003db95c9c468101af6b2a4d74708ad5cfcaeac3", + "gitDir": "test/corpus/repos/javascript", + "sha2": "898d1deeb737fc056929282ccce44a7aaef55034" +} +,{ + "testCaseDescription": "javascript-while-statement-delete-insert-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 8 + ], + "name": "while-statement.js", + "end": [ + 1, + 9 + ] + }, + { + "start": [ + 1, + 8 + ], + "name": "while-statement.js", + "end": [ + 1, + 9 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 13 + ], + "name": "while-statement.js", + "end": [ + 1, + 14 + ] + }, + { + "start": [ + 1, + 13 + ], + "name": "while-statement.js", + "end": [ + 1, + 14 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier in the b() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "898d1deeb737fc056929282ccce44a7aaef55034", + "gitDir": "test/corpus/repos/javascript", + "sha2": "77e4e9b64b3327f448bb03592ae0db023aa4aa1d" +} +,{ + "testCaseDescription": "javascript-while-statement-replacement-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "these": [ + { + "start": [ + 1, + 8 + ], + "name": "while-statement.js", + "end": [ + 1, + 9 + ] + }, + { + "start": [ + 1, + 8 + ], + "name": "while-statement.js", + "end": [ + 1, + 9 + ] + } + ] + }, + "summary": "Replaced the 'a' identifier with the 'b' identifier", + "tag": "JSONSummary" + }, + { + "span": { + "these": [ + { + "start": [ + 1, + 13 + ], + "name": "while-statement.js", + "end": [ + 1, + 14 + ] + }, + { + "start": [ + 1, + 13 + ], + "name": "while-statement.js", + "end": [ + 1, + 14 + ] + } + ] + }, + "summary": "Replaced the 'b' identifier with the 'a' identifier in the a() function call", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "77e4e9b64b3327f448bb03592ae0db023aa4aa1d", + "gitDir": "test/corpus/repos/javascript", + "sha2": "6c00977dc68dc8709bce328c2cc8bfb7205793ff" +} +,{ + "testCaseDescription": "javascript-while-statement-delete-replacement-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "while-statement.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Deleted the 'b' while statement", + "tag": "JSONSummary" + }, + { + "span": { + "this": { + "start": [ + 2, + 1 + ], + "name": "while-statement.js", + "end": [ + 2, + 19 + ] + } + }, + "summary": "Deleted the 'a' while statement", + "tag": "JSONSummary" + }, + { + "span": { + "that": { + "start": [ + 2, + 1 + ], + "name": "while-statement.js", + "end": [ + 2, + 19 + ] + } + }, + "summary": "Added the 'b' while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "6c00977dc68dc8709bce328c2cc8bfb7205793ff", + "gitDir": "test/corpus/repos/javascript", + "sha2": "494bd2f0826ef9bb743f7873c597ed76a7714ec8" +} +,{ + "testCaseDescription": "javascript-while-statement-delete-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "while-statement.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Deleted the 'a' while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "494bd2f0826ef9bb743f7873c597ed76a7714ec8", + "gitDir": "test/corpus/repos/javascript", + "sha2": "98b4204c2fe7fb408f6c5911ce1a275af862f443" +} +,{ + "testCaseDescription": "javascript-while-statement-delete-rest-test", + "expectedResult": { + "changes": { + "while-statement.js": [ + { + "span": { + "this": { + "start": [ + 1, + 1 + ], + "name": "while-statement.js", + "end": [ + 1, + 19 + ] + } + }, + "summary": "Deleted the 'b' while statement", + "tag": "JSONSummary" + } + ] + }, + "errors": {} + }, + "filePaths": [ + "while-statement.js" + ], + "sha1": "98b4204c2fe7fb408f6c5911ce1a275af862f443", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a373c4a7201be2aa145e60cf15e0adfedc85aac5" +}] diff --git a/test/corpus/diff-summaries/template-string.json b/test/corpus/diff-summaries/template-string.json new file mode 100644 index 000000000..9d9838cc3 --- /dev/null +++ b/test/corpus/diff-summaries/template-string.json @@ -0,0 +1,105 @@ +[{ + "testCaseDescription": "javascript-template-string-insert-test", + "expectedResult": { + "changes": { + "template-string.js": [ "Added the '`one line`' template string" ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "e1be6714d1c7f731fec82d4a5f3ddcbd679bd231", + "gitDir": "test/corpus/repos/javascript", + "sha2": "01d9465e5591a489d8039350dc4a816baa76b02e" +} +,{ + "testCaseDescription": "javascript-template-string-replacement-insert-test", + "expectedResult": { + "changes": { + "template-string.js": [ "Added the '`multi line`' template string","Added the '`one line`' template string" ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "01d9465e5591a489d8039350dc4a816baa76b02e", + "gitDir": "test/corpus/repos/javascript", + "sha2": "741b9434a201fe7efb9ca1c215020769322ff122" +} +,{ + "testCaseDescription": "javascript-template-string-delete-insert-test", + "expectedResult": { + "changes": { + "template-string.js": [ "Added the '`one line`' template string","Deleted the '`multi line`' template string" ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "741b9434a201fe7efb9ca1c215020769322ff122", + "gitDir": "test/corpus/repos/javascript", + "sha2": "43dd5ba3b77caa88ae9bcb1cd5b7372e54176c65" +} +,{ + "testCaseDescription": "javascript-template-string-replacement-test", + "expectedResult": { + "changes": { + "template-string.js": [ "Added the '`mulit line`' template string","Deleted the '`one line`' template string" ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "43dd5ba3b77caa88ae9bcb1cd5b7372e54176c65", + "gitDir": "test/corpus/repos/javascript", + "sha2": "c685db7ae77b2b7c870c1278fdfee55b7afa2593" +} +,{ + "testCaseDescription": "javascript-template-string-delete-replacement-test", + "expectedResult": { + "changes": { + "template-string.js": [ "Deleted the '`multi line`' template string","Added the '`multi line`' template string","Deleted the '`one line`' template string" ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "c685db7ae77b2b7c870c1278fdfee55b7afa2593", + "gitDir": "test/corpus/repos/javascript", + "sha2": "8da41cffe4b13838c58f6f8e1affdc4ef8235558" +} +,{ + "testCaseDescription": "javascript-template-string-delete-test", + "expectedResult": { + "changes": { + "template-string.js": [ "Deleted the '`one line`' template string" ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "8da41cffe4b13838c58f6f8e1affdc4ef8235558", + "gitDir": "test/corpus/repos/javascript", + "sha2": "a27b0ea7b83d6c787a5bb24b1471364ada9fcc92" +} +,{ + "testCaseDescription": "javascript-template-string-delete-rest-test", + "expectedResult": { + "changes": { + "template-string.js": [ "Deleted the '`multi line`' template string" ] + }, + "errors": {} + }, + "filePaths": [ + "template-string.js" + ], + "sha1": "a27b0ea7b83d6c787a5bb24b1471364ada9fcc92", + "gitDir": "test/corpus/repos/javascript", + "sha2": "06b8c5b42b801f6855033fe4eafea2ee9fb2cef9" +}] diff --git a/test/corpus/generated/javascript.json b/test/corpus/generated/javascript.json new file mode 100644 index 000000000..f76c04ee9 --- /dev/null +++ b/test/corpus/generated/javascript.json @@ -0,0 +1,422 @@ +[ + { + "repoPath": "test/corpus/repos/javascript", + "repoUrl": "https://github.com/rewinfrey/javascript.git", + "language": "javascript", + "syntaxes": [ + { + "syntax": "object", + "repoFilePath": "object.js", + "insert": "{ \"key1\": \"value1\" };", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/object.json", + "replacement": "{ \"key1\": \"value1\", \"key2\": \"value2\", \"key3\": \"3.0\" };" + }, + { + "syntax": "anonymous-function", + "repoFilePath": "anonymous-function.js", + "insert": "function(a,b) { return a + b; }", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/anonymous-function.json", + "replacement": "function(b,c) { return b * c; }" + }, + { + "syntax": "anonymous-parameterless-function", + "repoFilePath": "anonymous-parameterless-function.js", + "insert": "function() { return 'hi'; }", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/anonymous-parameterless-function.json", + "replacement": "function() { return 'hello'; }" + }, + { + "syntax": "objects-with-methods", + "repoFilePath": "objects-with-methods.js", + "insert": "{ add(a, b) { return a + b; } };", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/object-with-methods.json", + "replacement": "{ subtract(a, b) { return a - b; } };" + }, + { + "syntax": "string", + "repoFilePath": "string.js", + "insert": "'A string with \"double\" quotes';", + "replacement": "'A different string with \"double\" quotes';", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/string.json" + }, + { + "syntax": "number", + "repoFilePath": "number.js", + "insert": "101", + "replacement": "102", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/number.json" + }, + { + "syntax": "variable", + "repoFilePath": "variable.js", + "insert": "theVar;", + "replacement": "theVar2", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/variable.json" + }, + { + "syntax": "identifier", + "repoFilePath": "identifier.js", + "insert": "theVar;", + "replacement": "theVar2", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/identifier.json" + }, + { + "syntax": "this-expression", + "repoFilePath": "this-expression.js", + "insert": "this;", + "replacement": "return this;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/this-expression.json" + }, + { + "syntax": "null", + "repoFilePath": "null.js", + "insert": "null;", + "replacement": "return null;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/null.json" + }, + { + "syntax": "undefined", + "repoFilePath": "undefined.js", + "insert": "undefined;", + "replacement": "return undefined;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/undefined.json" + }, + { + "syntax": "true", + "repoFilePath": "true.js", + "insert": "true;", + "replacement": "return true;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/true.json" + }, + { + "syntax": "false", + "repoFilePath": "false.js", + "insert": "false;", + "replacement": "return false;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/false.json" + }, + { + "syntax": "class", + "repoFilePath": "class.js", + "insert": "class Foo { static one(a) { return a; }; two(b) { return b; } three(c) { return c; } }", + "replacement": "class Foo { static foo(a) { return a; }; bar(b) { return b; } baz(c) { return c; } }", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/class.json" + }, + { + "syntax": "array", + "repoFilePath": "array.js", + "insert": "[ \"item1\" ];", + "replacement": "[ \"item1\", \"item2\" ];", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/array.json" + }, + { + "syntax": "function", + "repoFilePath": "function.js", + "insert": "function(arg1, arg2) { arg2; };", + "replacement": "function(arg1, arg2) { arg1; };", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/function.json" + }, + { + "syntax": "arrow-function", + "repoFilePath": "arrow-function.js", + "insert": "(f, g) => { return h; };", + "replacement": "(f, g) => { return g; };", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/arrow-function.json" + }, + { + "syntax": "generator-function", + "repoFilePath": "generator-function.js", + "insert": "function *generateStuff(arg1, arg2) { yield; yield arg2; };", + "replacement": "function *generateNewStuff(arg1, arg2) { yield; yield arg2; };", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/generator-function.json" + }, + { + "syntax": "named-function", + "repoFilePath": "named-function.js", + "insert": "function myFunction(arg1, arg2) { arg2; };", + "replacement": "function anotherFunction() { return false; };", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/named-function.json" + }, + { + "syntax": "member-access", + "repoFilePath": "member-access.js", + "insert": "x.someProperty;", + "replacement": "x.someOtherProperty", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/member-access.json" + }, + { + "syntax": "subscript-access-variable", + "repoFilePath": "subscript-access-variable.js", + "insert": "x[someVariable];", + "replacement": "x[someOtherVariable];", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/subscript-access-variable.json" + }, + { + "syntax": "subscript-access-string", + "repoFilePath": "subscript-access-string.js", + "insert": "x[\"some-string\"];", + "replacement": "x[\"some-other-string\"];", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/subscript-access-string.json" + }, + { + "syntax": "chained-property-access", + "repoFilePath": "chained-property-access.js", + "insert": "return returned.promise().done( newDefer.resolve ).fail( newDefer.reject )", + "replacement": "return returned.promise().done( otherDefer.resolve ).fail( otherDefer.reject )", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/chained-property-access.json" + }, + { + "syntax": "chained-callbacks", + "repoFilePath": "chained-callbacks.js", + "insert": "this.map(function (a) { return a.b; })", + "replacement": "this.reduce(function (a) { return b.a; })", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/chained-callbacks.json" + }, + { + "syntax": "function-call", + "repoFilePath": "function-call.js", + "insert": "someFunction(arg1, \"arg2\");", + "replacement": "someFunction(arg1, \"arg3\");", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/function-call.json" + }, + { + "syntax": "method-call", + "repoFilePath": "method-call.js", + "insert": "object.someMethod(arg1, \"arg2\");", + "replacement": "object.someMethod(arg1, \"arg3\");", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/method-call.json" + }, + { + "syntax": "function-call-args", + "repoFilePath": "function-call-args.js", + "insert": "someFunction(1, \"string\", function(a,b) { console.log(a); return b; }, true)", + "replacement": "someFunction(1, \"otherString\", function(b,c) { console.log(b); return c; }, false)", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/function-call-args.json" + }, + { + "syntax": "constructor-call", + "repoFilePath": "constructor-call.js", + "insert": "new module.Klass(1, \"two\");", + "replacement": "new module.Klass(1, \"three\");", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/constructor-call.json" + }, + { + "syntax": "math-operator", + "repoFilePath": "math-operator.js", + "insert": "i + j * 3 - j % 5;", + "replacement": "i + j * 2 - j % 4;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/math-operator.json" + }, + { + "syntax": "boolean-operator", + "repoFilePath": "boolean-operator.js", + "insert": "i || j;", + "replacement": "i && j;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/boolean-operator.json" + }, + { + "syntax": "bitwise-operator", + "repoFilePath": "bitwise-operator.js", + "insert": "i >> j;", + "replacement": "i >> k;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/bitwise-operator.json" + }, + { + "syntax": "relational-operator", + "repoFilePath": "relational-operator.js", + "insert": "x < y;", + "replacement": "x <= y;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/relational-operator.json" + }, + { + "syntax": "for-statement", + "repoFilePath": "for-statement.js", + "insert": "for (i = 0, init(); i < 10; i++) { log(i); }", + "replacement": "for (i = 0, init(); i < 100; i++) { log(i); }", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/for-statement.json" + }, + { + "syntax": "assignment", + "repoFilePath": "assignment.js", + "insert": "x = 0;", + "replacement": "x = 1;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/assignment.json" + }, + { + "syntax": "member-access-assignment", + "repoFilePath": "member-access-assignment.js", + "insert": "y.x = 0;", + "replacement": "y.x = 1;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/member-access-assignment.json" + }, + { + "syntax": "subscript-access-assignment", + "repoFilePath": "subscript-access-assignment.js", + "insert": "y[\"x\"] = 0;", + "replacement": "y[\"x\"] = 1;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/subscript-access-assignment.json" + }, + { + "syntax": "comma-operator", + "repoFilePath": "comma-operator.js", + "insert": "a = 1, b = 2;", + "replacement": "c = {d: (3, 4 + 5, 6)};", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/comma-operator.json" + }, + { + "syntax": "ternary", + "repoFilePath": "ternary.js", + "insert": "condition ? case1 : case2;", + "replacement": "x.y = some.condition ? some.case : some.other.case;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/ternary.json" + }, + { + "syntax": "type-operator", + "repoFilePath": "type-operator.js", + "insert": "typeof x;", + "replacement": "x instanceof String;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/type-operator.json" + }, + { + "syntax": "delete-operator", + "repoFilePath": "delete-operator.js", + "insert": "delete thing['prop'];", + "replacement": "delete thing.prop", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/delete-operator.json" + }, + { + "syntax": "void-operator", + "repoFilePath": "void-operator.js", + "insert": "void b()", + "replacement": "void c()", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/void-operator.json" + }, + { + "syntax": "math-assignment-operator", + "repoFilePath": "math-assignment-operator.js", + "insert": "x += 1;", + "replacement": "x += 2;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/math-assignment-operator.json" + }, + { + "syntax": "for-loop-with-in-statement", + "repoFilePath": "for-loop-with-in-statement.js", + "insert": "for (key in something && i = 0; i < n; i++) { doSomething(); }", + "replacement": "for (otherKey in something && i = 0; i < n; i++) { doOtherSomething(); }", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/for-loop-with-in-statement.json" + }, + { + "syntax": "for-of-statement", + "repoFilePath": "for-of-statement.js", + "insert": "for (let item of items) { process(item); };", + "replacement": "for (let thing of things) { process(thing); };", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/for-of-statement.json" + }, + { + "syntax": "while-statement", + "repoFilePath": "while-statement.js", + "insert": "while (a) { b(); };", + "replacement": "while (b) { a(); };", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/while-statement.json" + }, + { + "syntax": "do-while-statement", + "repoFilePath": "do-while-statement.js", + "insert": "do { console.log(insert); } while (true);", + "replacement": "do { console.log(replacement); } while (false);", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/do-while-statement.json" + }, + { + "syntax": "return-statement", + "repoFilePath": "return-statement.js", + "insert": "return 5;", + "replacement": "return;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/return-statement.json" + }, + { + "syntax": "var-declaration", + "repoFilePath": "var-declaration.js", + "insert": "var x = 1;", + "replacement": "var x, y = {}, z;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/var-declaration.json" + }, + { + "syntax": "comment", + "repoFilePath": "comment.js", + "insert": "// This is a property", + "replacement": "/*\n * This is a method\n*/", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/comment.json" + }, + { + "syntax": "switch-statement", + "repoFilePath": "switch-statement.js", + "insert": "switch (1) { case 1: 1; case 2: 1; case 3: 3; };", + "replacement": "switch (2) { case 1: 1; case 2: 2; case 3: 3; };", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/switch-statement.json" + }, + { + "syntax": "throw-statement", + "repoFilePath": "throw-statement.js", + "insert": "throw new Error(\"uh oh\");", + "replacement": "throw new Error(\"oooooops\");", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/throw-statement.json" + }, + { + "syntax": "try-statement", + "repoFilePath": "try-statement.js", + "insert": "try { f; } catch { g; } finally { h; };", + "replacement": "try { f; } catch { h; } finally { g; };", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/try-statement.json" + }, + { + "syntax": "regex", + "repoFilePath": "regex.js", + "insert": "/one/g;", + "replacement": "/on[^/]afe/gim;", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/regex.json" + }, + { + "syntax": "if", + "repoFilePath": "if.js", + "insert": "if (x) { log(y); }", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/if.json", + "replacement": "if (a.b) { log(c); d; }" + }, + { + "syntax": "if-else", + "repoFilePath": "if-else.js", + "insert": "if (x) y; else if (a) b;", + "replacement": "if (a) { c; d; } else { e; }", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/if-else.json" + }, + { + "syntax": "template-string", + "repoFilePath": "template-string.js", + "insert": "`one line`", + "replacement": "`multi line`", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/template-string.json" + }, + { + "syntax": "for-in-statement", + "repoFilePath": "for-in-statement.js", + "insert": "for (thing in things) { thing(); }", + "replacement": "for (item in items) { item(); }", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/for-in-statement.json" + }, + { + "syntax": "nested-functions", + "repoFilePath": "nested-functions.js", + "insert": "function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg3); console.log(arg4); } }", + "replacement": "function parent (arg1, arg2) { function child (arg3, arg4) { console.log(arg1); console.log(arg2); } }", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/nested-functions.json" + }, + { + "syntax": "nested-do-while-in-function", + "repoFilePath": "nested-do-while-in-function.js", + "insert": "function f(arg1, arg2) { do { something(arg1); } while (arg2); }", + "replacement": "function f(arg1, arg2) { do { something(arg2); } while (arg1); }", + "testCaseFilePath": "test/corpus/diff-summaries/javascript/nested-do-while-in-function.json" + } + ] + } +] diff --git a/test/corpus/generators/.gitkeep b/test/corpus/generators/.gitkeep new file mode 100644 index 000000000..e69de29bb diff --git a/test/corpus/repos/javascript b/test/corpus/repos/javascript new file mode 160000 index 000000000..14310ea87 --- /dev/null +++ b/test/corpus/repos/javascript @@ -0,0 +1 @@ +Subproject commit 14310ea870b177f2187e152498699c8cd1b039f3 diff --git a/vendor/tree-sitter-parsers b/vendor/tree-sitter-parsers index 8348194cc..de7bfb996 160000 --- a/vendor/tree-sitter-parsers +++ b/vendor/tree-sitter-parsers @@ -1 +1 @@ -Subproject commit 8348194cc52b4b9fd61e3988b9526b54ebfef920 +Subproject commit de7bfb99606c9b5151d9e877d43c73cd9d0a44e9