mirror of
https://github.com/github/semantic.git
synced 2024-12-25 07:55:12 +03:00
Merge pull request #864 from github/project-reorg
Project reorg and rename binary to semantic-diff
This commit is contained in:
commit
db2e3cf236
@ -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(?<file>/[^:]+):(?<line>\d+):((?<col>\d+):)?
|
||||
|
3
.gitmodules
vendored
3
.gitmodules
vendored
@ -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
|
||||
|
@ -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:
|
||||
|
246
app/GenerateTestCases.hs
Normal file
246
app/GenerateTestCases.hs
Normal file
@ -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 [Text]))]
|
||||
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 [Text]), Maybe (Map Text [Text]))
|
||||
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 } ""
|
3
app/Main.hs
Normal file
3
app/Main.hs
Normal file
@ -0,0 +1,3 @@
|
||||
module Main (main)
|
||||
where
|
||||
import SemanticDiff (main)
|
@ -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"
|
||||
]
|
||||
|
12
bench/SemanticDiffPar.hs
Normal file
12
bench/SemanticDiffPar.hs
Normal file
@ -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))
|
@ -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
|
||||
|
156
src/SemanticDiff.hs
Normal file
156
src/SemanticDiff.hs
Normal file
@ -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
|
31
test/JSONTestCase.hs
Normal file
31
test/JSONTestCase.hs
Normal file
@ -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 [Text]))
|
||||
} deriving (Show, Generic, FromJSON)
|
||||
|
||||
instance ToJSON JSONTestCase where
|
||||
toEncoding = genericToEncoding defaultOptions
|
53
test/SemanticGitDiffSpec.hs
Normal file
53
test/SemanticGitDiffSpec.hs
Normal file
@ -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 [Text])) -> Either String (Map Text (Map Text [Text])) -> 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 [Text])) -> Either String (Map Text (Map Text [Text])) -> 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")
|
9
test/SpecIntegration.hs
Normal file
9
test/SpecIntegration.hs
Normal file
@ -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
|
0
test/corpus/diff-summaries-todo/javascript/.gitkeep
Normal file
0
test/corpus/diff-summaries-todo/javascript/.gitkeep
Normal file
@ -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"
|
||||
}]
|
@ -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"
|
||||
}]
|
127
test/corpus/diff-summaries/javascript/anonymous-function.json
Normal file
127
test/corpus/diff-summaries/javascript/anonymous-function.json
Normal file
@ -0,0 +1,127 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-anonymous-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Added an anonymous (a,b) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "682c9bc7b6e0bdf863dcaa32f63278a65cbae946",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "73bf5733fae4a699c86b187a1bdb12c4877a4001"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-function-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Added an anonymous (b,c) function",
|
||||
"Added an anonymous (a,b) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "73bf5733fae4a699c86b187a1bdb12c4877a4001",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "36e07108362ec6423e60b1d917917c3e09234360"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Replaced the 'c' identifier with the 'a' identifier",
|
||||
"Replaced the 'b' identifier with the 'a' identifier",
|
||||
"Replaced the 'c' identifier with the 'b' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "36e07108362ec6423e60b1d917917c3e09234360",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "84fcb25dc4d64a74bc654b68eb60c6de6bbe1d9e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Deleted the 'a' identifier",
|
||||
"Added the 'c' identifier",
|
||||
"Replaced the 'a' identifier with the 'b' identifier",
|
||||
"Replaced the 'b' identifier with the 'c' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "84fcb25dc4d64a74bc654b68eb60c6de6bbe1d9e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e311f46d65600e45ad1c9d28741d7138a20cd84a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Deleted an anonymous (b,c) function",
|
||||
"Deleted an anonymous (a,b) function",
|
||||
"Added an anonymous (b,c) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "e311f46d65600e45ad1c9d28741d7138a20cd84a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "02db7fdb98d56e46e5a10e10b3881339a881bf9a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Deleted an anonymous (a,b) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "02db7fdb98d56e46e5a10e10b3881339a881bf9a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "83545a313b0dcb2e84df65aa0e2a1a0ca0ecc5b7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Deleted an anonymous (b,c) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "83545a313b0dcb2e84df65aa0e2a1a0ca0ecc5b7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4fc6bdfea8bbd17d810f8687b2c6ffacc375b201"
|
||||
}]
|
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Added an anonymous function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "4fc6bdfea8bbd17d810f8687b2c6ffacc375b201",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5daf22f20c7d289bdbe321413e31069a6ea87076"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Added an anonymous function",
|
||||
"Added an anonymous function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "5daf22f20c7d289bdbe321413e31069a6ea87076",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3002a6ae8edbf89f70b807e942594466f5ddfdec"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Replaced the 'hello' string with the 'hi' string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "3002a6ae8edbf89f70b807e942594466f5ddfdec",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "87d4de08da4b84f7a9e8daca8c90e8a6ab081126"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Replaced the 'hi' string with the 'hello' string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "87d4de08da4b84f7a9e8daca8c90e8a6ab081126",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a1f6c1aed67d1ec8b248438a37ab62a2dcdb6cdc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Deleted an anonymous function",
|
||||
"Deleted an anonymous function",
|
||||
"Added an anonymous function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "a1f6c1aed67d1ec8b248438a37ab62a2dcdb6cdc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ae5fd8ad80227a1094660c48e32bda31c2921d1b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Deleted an anonymous function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "ae5fd8ad80227a1094660c48e32bda31c2921d1b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a4ff0bbb32f90e6a1e58dd11cb9b1dee15edde15"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Deleted an anonymous function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "a4ff0bbb32f90e6a1e58dd11cb9b1dee15edde15",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7451453939a71bed1ff4fdd7d49f1541b5250916"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/array.json
Normal file
122
test/corpus/diff-summaries/javascript/array.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-array-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Added the '[ \"item1\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "dd7ca7adcacbe84df962afb2cacb889e9c36555e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0418b13c26f0d7b4066fed6e2c96b7e4d7089ac3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Added the '[ \"item1\", \"item2\" ]' array",
|
||||
"Added the '[ \"item1\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "0418b13c26f0d7b4066fed6e2c96b7e4d7089ac3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0b4952dc07e32e0849db5543eee8abdb5b4248a7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Deleted the \"item2\" string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "0b4952dc07e32e0849db5543eee8abdb5b4248a7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7ef888c9a5c940124390e379435f37177f9b4f4c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Added the \"item2\" string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "7ef888c9a5c940124390e379435f37177f9b4f4c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0efeca94b446b67eee94d0bf04e7f8c2c026b22f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Deleted the '[ \"item1\", \"item2\" ]' array",
|
||||
"Deleted the '[ \"item1\" ]' array",
|
||||
"Added the '[ \"item1\", \"item2\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "0efeca94b446b67eee94d0bf04e7f8c2c026b22f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6d22167393268e61aa06e0b171519476dc16bdac"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Deleted the '[ \"item1\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "6d22167393268e61aa06e0b171519476dc16bdac",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "efff6458dae06c9af9ecb08c046fc0ff4f745337"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Deleted the '[ \"item1\", \"item2\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "efff6458dae06c9af9ecb08c046fc0ff4f745337",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "95af18d8919ff9cfae6d2f0c604ed1a6ad724386"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/arrow-function.json
Normal file
122
test/corpus/diff-summaries/javascript/arrow-function.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-arrow-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Added an anonymous (f, g) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "fa671e38d081b4d20788ab07afa49516b99d2a5f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b86c50d4d1af5a196ea5e41c5dff6d0e14dcb75e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-arrow-function-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Added an anonymous (f, g) function",
|
||||
"Added an anonymous (f, g) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "b86c50d4d1af5a196ea5e41c5dff6d0e14dcb75e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "799ac821b899058d26e95ef1831789f94bd13a06"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-arrow-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Replaced the 'g' identifier with the 'h' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "799ac821b899058d26e95ef1831789f94bd13a06",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "82e2293cbc203b5a493e66cf447926c9907392b1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-arrow-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Replaced the 'h' identifier with the 'g' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "82e2293cbc203b5a493e66cf447926c9907392b1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e91661096c6894cdc1724ae5234367d40812ed28"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-arrow-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Deleted an anonymous (f, g) function",
|
||||
"Deleted an anonymous (f, g) function",
|
||||
"Added an anonymous (f, g) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "e91661096c6894cdc1724ae5234367d40812ed28",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d3907ca3d7251faf305da1c2eda1b04618fedbb6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-arrow-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Deleted an anonymous (f, g) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "d3907ca3d7251faf305da1c2eda1b04618fedbb6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1104ba97b43b38c0284a25698b781c18ea18f99b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-arrow-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Deleted an anonymous (f, g) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "1104ba97b43b38c0284a25698b781c18ea18f99b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "907b5c72373793066771c9e049b754b7508f457a"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/assignment.json
Normal file
122
test/corpus/diff-summaries/javascript/assignment.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-assignment-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Added the 'x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "6f17186b61d196c816fb294ce4cbc82afd93342f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2caf1b29d2e2e6e126c3dc4c463cc27467bebfcd"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Added the 'x' assignment",
|
||||
"Added the 'x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "2caf1b29d2e2e6e126c3dc4c463cc27467bebfcd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9db73a5d30fff52a2d14d5b425798aae70c6e9c3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Replaced '1' with '0' in an assignment to x"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "9db73a5d30fff52a2d14d5b425798aae70c6e9c3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "59a663d83db6ba1fefb255fed0d46489213e71c0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Replaced '0' with '1' in an assignment to x"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "59a663d83db6ba1fefb255fed0d46489213e71c0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "74f9f78bafc2231891faf67ed1c6281936c6d562"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Deleted the 'x' assignment",
|
||||
"Deleted the 'x' assignment",
|
||||
"Added the 'x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "74f9f78bafc2231891faf67ed1c6281936c6d562",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c9c85158a4d11bf96e79b099cae6285171e680cc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Deleted the 'x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "c9c85158a4d11bf96e79b099cae6285171e680cc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b30bb512e3ffe02430c904f2ad0f3d446db64776"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Deleted the 'x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "b30bb512e3ffe02430c904f2ad0f3d446db64776",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "410d8b5edf1e9ab9fc842fe489424a7b03f57d1c"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/bitwise-operator.json
Normal file
122
test/corpus/diff-summaries/javascript/bitwise-operator.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-bitwise-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Added the 'i >> j' bitwise operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "64908cefe1f4a89c4491d3512ab5bb6fb4625096",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b2c41648296aa2e03852bb5e91537514cc293b1c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-bitwise-operator-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Added the 'i >> k' bitwise operator",
|
||||
"Added the 'i >> j' bitwise operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "b2c41648296aa2e03852bb5e91537514cc293b1c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5375465c178bf87a3aea5871ee611c582f002a00"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-bitwise-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Replaced the 'k' identifier with the 'j' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "5375465c178bf87a3aea5871ee611c582f002a00",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "928612908dfa572b054105ff4bdb95a130d09264"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-bitwise-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Replaced the 'j' identifier with the 'k' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "928612908dfa572b054105ff4bdb95a130d09264",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d4d3e2daa8fdef77b991876e30d2104299e22eca"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-bitwise-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Deleted the 'i >> k' bitwise operator",
|
||||
"Deleted the 'i >> j' bitwise operator",
|
||||
"Added the 'i >> k' bitwise operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "d4d3e2daa8fdef77b991876e30d2104299e22eca",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bf3663604c950ac71bf797dcd0cf66b091fef643"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-bitwise-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Deleted the 'i >> j' bitwise operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "bf3663604c950ac71bf797dcd0cf66b091fef643",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "399df95cd0f9607de8c8309c462996e5d3bfda59"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-bitwise-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Deleted the 'i >> k' bitwise operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "399df95cd0f9607de8c8309c462996e5d3bfda59",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "734a1520f6190913ebe3373ef3eaea2eb8fa32ac"
|
||||
}]
|
112
test/corpus/diff-summaries/javascript/boolean-operator.json
Normal file
112
test/corpus/diff-summaries/javascript/boolean-operator.json
Normal file
@ -0,0 +1,112 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-boolean-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"boolean-operator.js": [
|
||||
"Added the 'i || j' boolean operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"boolean-operator.js"
|
||||
],
|
||||
"sha1": "59296bb55e2a8b7e4618367d4a796b089c2da907",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "20b8ab7a83965d0e21cc9f83d4b73eada57573f5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-boolean-operator-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"boolean-operator.js": [
|
||||
"Added the 'i && j' boolean operator",
|
||||
"Added the 'i || j' boolean operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"boolean-operator.js"
|
||||
],
|
||||
"sha1": "20b8ab7a83965d0e21cc9f83d4b73eada57573f5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0ae891acc39e1ec380c35b9a3c99d042d9265191"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-boolean-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"boolean-operator.js"
|
||||
],
|
||||
"sha1": "0ae891acc39e1ec380c35b9a3c99d042d9265191",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4a4312c7aec5b34ff98d56611a94e97935c3c187"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-boolean-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"boolean-operator.js"
|
||||
],
|
||||
"sha1": "4a4312c7aec5b34ff98d56611a94e97935c3c187",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f9faf3b8fbb063cf2e874d2ac30e3dbf1f55bb4a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-boolean-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"boolean-operator.js": [
|
||||
"Deleted the 'i && j' boolean operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"boolean-operator.js"
|
||||
],
|
||||
"sha1": "f9faf3b8fbb063cf2e874d2ac30e3dbf1f55bb4a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "14713f00c83622e83ad8357796897b5bd0df10ff"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-boolean-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"boolean-operator.js": [
|
||||
"Deleted the 'i || j' boolean operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"boolean-operator.js"
|
||||
],
|
||||
"sha1": "14713f00c83622e83ad8357796897b5bd0df10ff",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e5170b8871a808f3c4fd38ea1b5d229e13de0552"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-boolean-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"boolean-operator.js": [
|
||||
"Deleted the 'i && j' boolean operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"boolean-operator.js"
|
||||
],
|
||||
"sha1": "e5170b8871a808f3c4fd38ea1b5d229e13de0552",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "64908cefe1f4a89c4491d3512ab5bb6fb4625096"
|
||||
}]
|
126
test/corpus/diff-summaries/javascript/chained-callbacks.json
Normal file
126
test/corpus/diff-summaries/javascript/chained-callbacks.json
Normal file
@ -0,0 +1,126 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-chained-callbacks-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Added the 'this.map(…)' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "459e0f3fa51c5b79bdb6174e3a566f5075a7958c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5fc6d187080f87e95d1c04da36d3fa6fa529d2da"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-callbacks-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Added the 'this.reduce(…)' method call",
|
||||
"Added the 'this.map(…)' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "5fc6d187080f87e95d1c04da36d3fa6fa529d2da",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b255343a7bcf0e2428f408d49f2039300df13124"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-callbacks-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Replaced the 'reduce' identifier with the 'map' identifier in the this.map(…) method call",
|
||||
"Replaced the 'b' identifier with the 'a' identifier in the this.map(…) method call",
|
||||
"Replaced the 'a' identifier with the 'b' identifier in the this.map(…) method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "b255343a7bcf0e2428f408d49f2039300df13124",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "426b1a7459cb38a7cca2a0f1253a716b87f138d6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-callbacks-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Replaced the 'map' identifier with the 'reduce' identifier in the this.reduce(…) method call",
|
||||
"Replaced the 'a' identifier with the 'b' identifier in the this.reduce(…) method call",
|
||||
"Replaced the 'b' identifier with the 'a' identifier in the this.reduce(…) method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "426b1a7459cb38a7cca2a0f1253a716b87f138d6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1332c6fba2a66240ab8f1796e14d47943f5a4ec5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-callbacks-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Deleted the 'this.reduce(…)' method call",
|
||||
"Deleted the 'this.map(…)' method call",
|
||||
"Added the 'this.reduce(…)' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "1332c6fba2a66240ab8f1796e14d47943f5a4ec5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3df2da65bb58f3c7f30b820a26b2df8d05091c9b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-callbacks-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Deleted the 'this.map(…)' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "3df2da65bb58f3c7f30b820a26b2df8d05091c9b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6d3b3398548b6ced3ad120440b9d006cfdb01778"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-callbacks-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Deleted the 'this.reduce(…)' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "6d3b3398548b6ced3ad120440b9d006cfdb01778",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c65612605de8c1f239d5529a0761a1fbd88a5833"
|
||||
}]
|
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-chained-property-access-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-property-access.js": [
|
||||
"Added the 'returned.promise().done(…).fail(…)' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-property-access.js"
|
||||
],
|
||||
"sha1": "2af71438d83e47601320a632ea6bc26ae90a70d8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d1bfac469e4c9509a14644ecdc1553b3b620e967"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-property-access.js": [
|
||||
"Added the 'returned.promise().done(…).fail(…)' return statement",
|
||||
"Added the 'returned.promise().done(…).fail(…)' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-property-access.js"
|
||||
],
|
||||
"sha1": "d1bfac469e4c9509a14644ecdc1553b3b620e967",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9438bdffda260fe6e0c98656fa39e79b0bab8460"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-property-access.js": [
|
||||
"Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…) method call",
|
||||
"Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…).fail(…) method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-property-access.js"
|
||||
],
|
||||
"sha1": "9438bdffda260fe6e0c98656fa39e79b0bab8460",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "272aa7840bb81dbed31788bf0425e15e01e7a259"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-property-access.js": [
|
||||
"Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…) method call",
|
||||
"Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…).fail(…) method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-property-access.js"
|
||||
],
|
||||
"sha1": "272aa7840bb81dbed31788bf0425e15e01e7a259",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c2a33ddcaab66990c1ff5e2aba103cb8a4c0fe3d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-property-access.js": [
|
||||
"Deleted the 'returned.promise().done(…).fail(…)' return statement",
|
||||
"Deleted the 'returned.promise().done(…).fail(…)' return statement",
|
||||
"Added the 'returned.promise().done(…).fail(…)' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-property-access.js"
|
||||
],
|
||||
"sha1": "c2a33ddcaab66990c1ff5e2aba103cb8a4c0fe3d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2b95977c9286201862d75802aa5404079a99c92c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-property-access.js": [
|
||||
"Deleted the 'returned.promise().done(…).fail(…)' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-property-access.js"
|
||||
],
|
||||
"sha1": "2b95977c9286201862d75802aa5404079a99c92c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9b8f13b61dd23ca8cccd42bdb9756ab7d99e1141"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-property-access.js": [
|
||||
"Deleted the 'returned.promise().done(…).fail(…)' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-property-access.js"
|
||||
],
|
||||
"sha1": "9b8f13b61dd23ca8cccd42bdb9756ab7d99e1141",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "459e0f3fa51c5b79bdb6174e3a566f5075a7958c"
|
||||
}]
|
126
test/corpus/diff-summaries/javascript/class.json
Normal file
126
test/corpus/diff-summaries/javascript/class.json
Normal file
@ -0,0 +1,126 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-class-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Added the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "113297963da10f52091760ca956952f15b35ba51",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9148b4f9a222473762d0d6c67a40ac2c907986a5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Added the 'Foo' class",
|
||||
"Added the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "9148b4f9a222473762d0d6c67a40ac2c907986a5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a1a53afb9fb953bb16cf3915bd673dd2210df5e3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Replaced the 'foo' identifier with the 'one' identifier in the one method of the 'Foo' class",
|
||||
"Replaced the 'bar' identifier with the 'two' identifier in the two method of the 'Foo' class",
|
||||
"Replaced the 'baz' identifier with the 'three' identifier in the three method of the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "a1a53afb9fb953bb16cf3915bd673dd2210df5e3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c30d02089fadff15504ab7eb24ec08ea54275adf"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Replaced the 'one' identifier with the 'foo' identifier in the foo method of the 'Foo' class",
|
||||
"Replaced the 'two' identifier with the 'bar' identifier in the bar method of the 'Foo' class",
|
||||
"Replaced the 'three' identifier with the 'baz' identifier in the baz method of the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "c30d02089fadff15504ab7eb24ec08ea54275adf",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b030bf052b6f7fa357abe4dbee065313f7edc80a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Deleted the 'Foo' class",
|
||||
"Deleted the 'Foo' class",
|
||||
"Added the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "b030bf052b6f7fa357abe4dbee065313f7edc80a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0db81f0fc457bb2428e9573ed7efb7f09da8a87d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Deleted the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "0db81f0fc457bb2428e9573ed7efb7f09da8a87d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6f32ee6b8596978e8971c32aa2d87f5ab8823d97"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Deleted the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "6f32ee6b8596978e8971c32aa2d87f5ab8823d97",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "dd7ca7adcacbe84df962afb2cacb889e9c36555e"
|
||||
}]
|
130
test/corpus/diff-summaries/javascript/comma-operator.json
Normal file
130
test/corpus/diff-summaries/javascript/comma-operator.json
Normal file
@ -0,0 +1,130 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-comma-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comma-operator.js": [
|
||||
"Added the 'a' assignment",
|
||||
"Added the 'b' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comma-operator.js"
|
||||
],
|
||||
"sha1": "5ed18af6b663f85d2635954f1488222c50b359d8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4ae3b71d859e658c90ea888937949623400dac76"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comma-operator-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comma-operator.js": [
|
||||
"Added the 'c' assignment",
|
||||
"Added the 'a' assignment",
|
||||
"Added the 'b' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comma-operator.js"
|
||||
],
|
||||
"sha1": "4ae3b71d859e658c90ea888937949623400dac76",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "98291d2c2ac04ef9019b6da99b6014b431a809e3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comma-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comma-operator.js": [
|
||||
"Added the 'a' assignment",
|
||||
"Added the 'b' assignment",
|
||||
"Deleted the 'c' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comma-operator.js"
|
||||
],
|
||||
"sha1": "98291d2c2ac04ef9019b6da99b6014b431a809e3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "19c516d95a66b98ce5668033444f14567417c165"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comma-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comma-operator.js": [
|
||||
"Added the 'c' assignment",
|
||||
"Deleted the 'a' assignment",
|
||||
"Deleted the 'b' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comma-operator.js"
|
||||
],
|
||||
"sha1": "19c516d95a66b98ce5668033444f14567417c165",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ca38c681438b9a57bd0bec37b1d5dbcda3eadc04"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comma-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comma-operator.js": [
|
||||
"Deleted the 'c' assignment",
|
||||
"Deleted the 'a' assignment",
|
||||
"Deleted the 'b' assignment",
|
||||
"Added the 'c' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comma-operator.js"
|
||||
],
|
||||
"sha1": "ca38c681438b9a57bd0bec37b1d5dbcda3eadc04",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "588c37fed796f266268fdbe0f2ce1e49427dda52"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comma-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comma-operator.js": [
|
||||
"Deleted the 'a' assignment",
|
||||
"Deleted the 'b' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comma-operator.js"
|
||||
],
|
||||
"sha1": "588c37fed796f266268fdbe0f2ce1e49427dda52",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4e8427023841064a12a6f8706d1e83584e0a4a66"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comma-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comma-operator.js": [
|
||||
"Deleted the 'c' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comma-operator.js"
|
||||
],
|
||||
"sha1": "4e8427023841064a12a6f8706d1e83584e0a4a66",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6f2be827ecaee324c13a7571522397d699609382"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/comment.json
Normal file
122
test/corpus/diff-summaries/javascript/comment.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-comment-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Added the '// This is a property' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "e797ca2c748a6d42d67875240942d0876fd66cbc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9b44781137dd99590dc0b1ee7f175d7554fc19c1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comment-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Added the '/*\n * This is a method\n*/' comment",
|
||||
"Added the '// This is a property' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "9b44781137dd99590dc0b1ee7f175d7554fc19c1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b7b5ac68f521105a55e5efbbc290762ae19e998a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comment-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Replaced the '/*\n * This is a method\n*/' comment with the '// This is a property' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "b7b5ac68f521105a55e5efbbc290762ae19e998a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f28812e795ef48e013b23d15cc250a11a65d1efb"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comment-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Replaced the '// This is a property' comment with the '/*\n * This is a method\n*/' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "f28812e795ef48e013b23d15cc250a11a65d1efb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "94d3258258fc5dda40f68012a4a29a0699ae7198"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comment-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Deleted the '/*\n * This is a method\n*/' comment",
|
||||
"Deleted the '// This is a property' comment",
|
||||
"Added the '/*\n * This is a method\n*/' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "94d3258258fc5dda40f68012a4a29a0699ae7198",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "054b25777313237a3548f17e75ddf0036c8c4b97"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comment-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Deleted the '// This is a property' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "054b25777313237a3548f17e75ddf0036c8c4b97",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "446ac1dc79acd4f137b6d2a6eb894cb3377f82a5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comment-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Deleted the '/*\n * This is a method\n*/' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "446ac1dc79acd4f137b6d2a6eb894cb3377f82a5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e744226ef998687c390e01091951dba025d40dfd"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/constructor-call.json
Normal file
122
test/corpus/diff-summaries/javascript/constructor-call.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-constructor-call-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Added the 'module.Klass(1, \"two\")' constructor"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "5aeda8deeda74b0668f87cbacb00781fd065df66",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a8abd84c17b7b6ef6544c6bb6dba4f083fff25ba"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-constructor-call-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Added the 'module.Klass(1, \"three\")' constructor",
|
||||
"Added the 'module.Klass(1, \"two\")' constructor"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "a8abd84c17b7b6ef6544c6bb6dba4f083fff25ba",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d678337aba38bab2811dd05bf3f795c73ef78898"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-constructor-call-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Replaced the \"three\" string with the \"two\" string in the module.Klass(1, \"two\") method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "d678337aba38bab2811dd05bf3f795c73ef78898",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "97304006d3644e339d95430d6223f840636736fd"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-constructor-call-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Replaced the \"two\" string with the \"three\" string in the module.Klass(1, \"three\") method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "97304006d3644e339d95430d6223f840636736fd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "587180153f18e624722447a1d833d401c0e42b94"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-constructor-call-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Deleted the 'module.Klass(1, \"three\")' constructor",
|
||||
"Deleted the 'module.Klass(1, \"two\")' constructor",
|
||||
"Added the 'module.Klass(1, \"three\")' constructor"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "587180153f18e624722447a1d833d401c0e42b94",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "79e6ed4f1e30269dc951316a6beef80a861cb3ff"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-constructor-call-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Deleted the 'module.Klass(1, \"two\")' constructor"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "79e6ed4f1e30269dc951316a6beef80a861cb3ff",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "677a713a36bc78813eb5d997c6d6ff3e1775ecbb"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-constructor-call-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Deleted the 'module.Klass(1, \"three\")' constructor"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "677a713a36bc78813eb5d997c6d6ff3e1775ecbb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5849813ca5290325ffe39d290e78a99104035304"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/delete-operator.json
Normal file
122
test/corpus/diff-summaries/javascript/delete-operator.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-delete-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Added the 'delete thing['prop']' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "e21de869506a2a72943755153b5a36862ef80f6c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1f8d975bbb26e218e0ab717fa15e281d5113bed0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-delete-operator-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Added the 'delete thing.prop' operator",
|
||||
"Added the 'delete thing['prop']' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "1f8d975bbb26e218e0ab717fa15e281d5113bed0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "26ab8336dfdf969e6b6f1101af8e0ce02c8194ae"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-delete-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Replaced the 'delete thing.prop' operator with the 'delete thing['prop']' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "26ab8336dfdf969e6b6f1101af8e0ce02c8194ae",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c5120a74c04555cb4b83147978a74e50f4316957"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-delete-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Replaced the 'delete thing['prop']' operator with the 'delete thing.prop' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "c5120a74c04555cb4b83147978a74e50f4316957",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "27ff42b5e0ebb7e5e74b5469b7104ece2e703a61"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-delete-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Deleted the 'delete thing.prop' operator",
|
||||
"Deleted the 'delete thing['prop']' operator",
|
||||
"Added the 'delete thing.prop' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "27ff42b5e0ebb7e5e74b5469b7104ece2e703a61",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "27d05d1fd6501544cb64fee600e5f9e4ce6cc8e8"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-delete-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Deleted the 'delete thing['prop']' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "27d05d1fd6501544cb64fee600e5f9e4ce6cc8e8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "346122ed1825595bf493f272828dfe9b0efbe029"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-delete-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Deleted the 'delete thing.prop' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "346122ed1825595bf493f272828dfe9b0efbe029",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "985f2a1f80a8f14a094977b3cb7b7954ea471f72"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/do-while-statement.json
Normal file
124
test/corpus/diff-summaries/javascript/do-while-statement.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-do-while-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"do-while-statement.js": [
|
||||
"Added the 'true' do/while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"do-while-statement.js"
|
||||
],
|
||||
"sha1": "d5cb38d1a4261f5dc4f97f8d7d0762f26dbd70e3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6c7dc6cd4f86a23d1794a455fa988dbde73e1e73"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-do-while-statement-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"do-while-statement.js": [
|
||||
"Added the 'false' do/while statement",
|
||||
"Added the 'true' do/while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"do-while-statement.js"
|
||||
],
|
||||
"sha1": "6c7dc6cd4f86a23d1794a455fa988dbde73e1e73",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5bfc5393302aafd0335c4637da356c7eb3d6ee60"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-do-while-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"do-while-statement.js": [
|
||||
"Replaced the 'replacement' identifier with the 'insert' identifier in the console.log(insert) method call",
|
||||
"Replaced 'false' with 'true' in the true do/while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"do-while-statement.js"
|
||||
],
|
||||
"sha1": "5bfc5393302aafd0335c4637da356c7eb3d6ee60",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e1246a7d640685a86e828d7a13edcc8a05fab646"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-do-while-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"do-while-statement.js": [
|
||||
"Replaced the 'insert' identifier with the 'replacement' identifier in the console.log(replacement) method call",
|
||||
"Replaced 'true' with 'false' in the false do/while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"do-while-statement.js"
|
||||
],
|
||||
"sha1": "e1246a7d640685a86e828d7a13edcc8a05fab646",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c2d637ee7fa9d1895a11dcf3a69a2be95ef0696a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-do-while-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"do-while-statement.js": [
|
||||
"Deleted the 'false' do/while statement",
|
||||
"Deleted the 'true' do/while statement",
|
||||
"Added the 'false' do/while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"do-while-statement.js"
|
||||
],
|
||||
"sha1": "c2d637ee7fa9d1895a11dcf3a69a2be95ef0696a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5a98e1e09d3f5606b52042f940b02fa4cfe37a40"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-do-while-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"do-while-statement.js": [
|
||||
"Deleted the 'true' do/while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"do-while-statement.js"
|
||||
],
|
||||
"sha1": "5a98e1e09d3f5606b52042f940b02fa4cfe37a40",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ba62765a2b3412b570f77b033b49247f45d8f57a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-do-while-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"do-while-statement.js": [
|
||||
"Deleted the 'false' do/while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"do-while-statement.js"
|
||||
],
|
||||
"sha1": "ba62765a2b3412b570f77b033b49247f45d8f57a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b36aa3066096eea1f721208040f74bc7cf9a3c9e"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/false.json
Normal file
124
test/corpus/diff-summaries/javascript/false.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-false-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Added 'false'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "1c81c54c83779f2e84d6c0820063f8b9def43147",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ea151512bcbdf0c138d5f4322a7434eae9e887a9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Added the 'false' return statement",
|
||||
"Added 'false'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "ea151512bcbdf0c138d5f4322a7434eae9e887a9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "573e0c673004a6d434d9c003d85c5c159d9d5cba"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Added 'false'",
|
||||
"Deleted the 'false' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "573e0c673004a6d434d9c003d85c5c159d9d5cba",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cfdd8768410568ec9352b1f87806f144129042b4"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Added the 'false' return statement",
|
||||
"Deleted 'false'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "cfdd8768410568ec9352b1f87806f144129042b4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e2d0840b14c3e50f0d5ddd5b4b77b40eaf425897"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Deleted the 'false' return statement",
|
||||
"Deleted 'false'",
|
||||
"Added the 'false' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "e2d0840b14c3e50f0d5ddd5b4b77b40eaf425897",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e9b890764a716dc2473668d693cd09606e5e4a56"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Deleted 'false'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "e9b890764a716dc2473668d693cd09606e5e4a56",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0bd6eb27b15176e66b217b8618bc1b7a31feaab9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Deleted the 'false' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "0bd6eb27b15176e66b217b8618bc1b7a31feaab9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "113297963da10f52091760ca956952f15b35ba51"
|
||||
}]
|
126
test/corpus/diff-summaries/javascript/for-in-statement.json
Normal file
126
test/corpus/diff-summaries/javascript/for-in-statement.json
Normal file
@ -0,0 +1,126 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-for-in-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-in-statement.js": [
|
||||
"Added the 'thing in things' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-in-statement.js"
|
||||
],
|
||||
"sha1": "ea2df743568a320252df57e60055d8d6e611d9e7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a5323182612a4cb0f0b9144c0d487138b7693844"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-in-statement-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-in-statement.js": [
|
||||
"Added the 'item in items' for statement",
|
||||
"Added the 'thing in things' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-in-statement.js"
|
||||
],
|
||||
"sha1": "a5323182612a4cb0f0b9144c0d487138b7693844",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b9a318024efbb6b16ef8a4cb62994e5cf53a9eed"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-in-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-in-statement.js": [
|
||||
"Replaced the 'item' identifier with the 'thing' identifier",
|
||||
"Replaced the 'items' identifier with the 'things' identifier",
|
||||
"Replaced the 'item' identifier with the 'thing' identifier in the thing() function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-in-statement.js"
|
||||
],
|
||||
"sha1": "b9a318024efbb6b16ef8a4cb62994e5cf53a9eed",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ef9b68774aa78ba393bcde5e4eaa58ec5c62ebba"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-in-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-in-statement.js": [
|
||||
"Replaced the 'thing' identifier with the 'item' identifier",
|
||||
"Replaced the 'things' identifier with the 'items' identifier",
|
||||
"Replaced the 'thing' identifier with the 'item' identifier in the item() function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-in-statement.js"
|
||||
],
|
||||
"sha1": "ef9b68774aa78ba393bcde5e4eaa58ec5c62ebba",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6a7c1aec72c990079fb74a2d88454879e0542b51"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-in-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-in-statement.js": [
|
||||
"Deleted the 'item in items' for statement",
|
||||
"Deleted the 'thing in things' for statement",
|
||||
"Added the 'item in items' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-in-statement.js"
|
||||
],
|
||||
"sha1": "6a7c1aec72c990079fb74a2d88454879e0542b51",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c77ceb93acf79d639f3d5f9b965a7e72811ef9a2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-in-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-in-statement.js": [
|
||||
"Deleted the 'thing in things' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-in-statement.js"
|
||||
],
|
||||
"sha1": "c77ceb93acf79d639f3d5f9b965a7e72811ef9a2",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e66118e2e67e731d3ff9d5cbff85d6e598a8fc9e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-in-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-in-statement.js": [
|
||||
"Deleted the 'item in items' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-in-statement.js"
|
||||
],
|
||||
"sha1": "e66118e2e67e731d3ff9d5cbff85d6e598a8fc9e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6798e4b37426ea6b88b61053b80ad8c9d1f52ab9"
|
||||
}]
|
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-for-loop-with-in-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-loop-with-in-statement.js": [
|
||||
"Added the 'key in something && i = 0; i < n; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-loop-with-in-statement.js"
|
||||
],
|
||||
"sha1": "d2af5ec3c3ad375060911e7ecab418524b362fb0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e60041368d83ff4b232dcfe04437d5fd462406ec"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-loop-with-in-statement.js": [
|
||||
"Added the 'otherKey in something && i = 0; i < n; i++' for statement",
|
||||
"Added the 'key in something && i = 0; i < n; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-loop-with-in-statement.js"
|
||||
],
|
||||
"sha1": "e60041368d83ff4b232dcfe04437d5fd462406ec",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "71b2b3e11200827268e624365f407da436799176"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-loop-with-in-statement.js": [
|
||||
"Replaced the 'otherKey' identifier with the 'key' identifier",
|
||||
"Replaced the 'doOtherSomething' identifier with the 'doSomething' identifier in the doSomething() function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-loop-with-in-statement.js"
|
||||
],
|
||||
"sha1": "71b2b3e11200827268e624365f407da436799176",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c6337bf9bb226248f0c6c0b11c4f27e9e8d98b2c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-loop-with-in-statement.js": [
|
||||
"Replaced the 'key' identifier with the 'otherKey' identifier",
|
||||
"Replaced the 'doSomething' identifier with the 'doOtherSomething' identifier in the doOtherSomething() function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-loop-with-in-statement.js"
|
||||
],
|
||||
"sha1": "c6337bf9bb226248f0c6c0b11c4f27e9e8d98b2c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6566987bc1a3bf7fa756fcebecc54fb98345f792"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-loop-with-in-statement.js": [
|
||||
"Deleted the 'otherKey in something && i = 0; i < n; i++' for statement",
|
||||
"Deleted the 'key in something && i = 0; i < n; i++' for statement",
|
||||
"Added the 'otherKey in something && i = 0; i < n; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-loop-with-in-statement.js"
|
||||
],
|
||||
"sha1": "6566987bc1a3bf7fa756fcebecc54fb98345f792",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d0d601c03abd9382571c881d66d4471078b447f5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-loop-with-in-statement.js": [
|
||||
"Deleted the 'key in something && i = 0; i < n; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-loop-with-in-statement.js"
|
||||
],
|
||||
"sha1": "d0d601c03abd9382571c881d66d4471078b447f5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "202bf0cbb2cd0a8fad734d182a89ce1932cffb37"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-loop-with-in-statement.js": [
|
||||
"Deleted the 'otherKey in something && i = 0; i < n; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-loop-with-in-statement.js"
|
||||
],
|
||||
"sha1": "202bf0cbb2cd0a8fad734d182a89ce1932cffb37",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "763e4c5cbb94150cd983bc1a0c9ecc2ff79a5bdf"
|
||||
}]
|
126
test/corpus/diff-summaries/javascript/for-of-statement.json
Normal file
126
test/corpus/diff-summaries/javascript/for-of-statement.json
Normal file
@ -0,0 +1,126 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-for-of-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-of-statement.js": [
|
||||
"Added the 'item of items' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-of-statement.js"
|
||||
],
|
||||
"sha1": "763e4c5cbb94150cd983bc1a0c9ecc2ff79a5bdf",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0913eaba361a34a9d301afe6645642399c068cb9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-of-statement-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-of-statement.js": [
|
||||
"Added the 'thing of things' for statement",
|
||||
"Added the 'item of items' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-of-statement.js"
|
||||
],
|
||||
"sha1": "0913eaba361a34a9d301afe6645642399c068cb9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cc040912f3d3c80c68d4990ae77549b0a71a6dd3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-of-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-of-statement.js": [
|
||||
"Replaced the 'thing' identifier with the 'item' identifier",
|
||||
"Replaced the 'things' identifier with the 'items' identifier",
|
||||
"Replaced the 'thing' identifier with the 'item' identifier in the process(item) function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-of-statement.js"
|
||||
],
|
||||
"sha1": "cc040912f3d3c80c68d4990ae77549b0a71a6dd3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b13a4bc950c6f5ba1a9f04998781592aca56a92b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-of-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-of-statement.js": [
|
||||
"Replaced the 'item' identifier with the 'thing' identifier",
|
||||
"Replaced the 'items' identifier with the 'things' identifier",
|
||||
"Replaced the 'item' identifier with the 'thing' identifier in the process(thing) function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-of-statement.js"
|
||||
],
|
||||
"sha1": "b13a4bc950c6f5ba1a9f04998781592aca56a92b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bc7c9f55c2f40743518f716dc418a2bdde62949b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-of-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-of-statement.js": [
|
||||
"Deleted the 'thing of things' for statement",
|
||||
"Deleted the 'item of items' for statement",
|
||||
"Added the 'thing of things' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-of-statement.js"
|
||||
],
|
||||
"sha1": "bc7c9f55c2f40743518f716dc418a2bdde62949b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8d5e15d9514988f4bbce77f2ccb591bef09e1438"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-of-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-of-statement.js": [
|
||||
"Deleted the 'item of items' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-of-statement.js"
|
||||
],
|
||||
"sha1": "8d5e15d9514988f4bbce77f2ccb591bef09e1438",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "13d21b3c47462b8a61fe51cdaed557b1ca62b780"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-of-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-of-statement.js": [
|
||||
"Deleted the 'thing of things' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-of-statement.js"
|
||||
],
|
||||
"sha1": "13d21b3c47462b8a61fe51cdaed557b1ca62b780",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "19910077ac4d4997c8d93c429177a77105905c9a"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/for-statement.json
Normal file
122
test/corpus/diff-summaries/javascript/for-statement.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-for-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-statement.js": [
|
||||
"Added the 'i = 0, init(); i < 10; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-statement.js"
|
||||
],
|
||||
"sha1": "2d85e84d4e6eb6192b5094b6934b9a76e854325b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9e13feb870cbb69188d12cb6eec660e77b7d5a9a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-statement-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-statement.js": [
|
||||
"Added the 'i = 0, init(); i < 100; i++' for statement",
|
||||
"Added the 'i = 0, init(); i < 10; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-statement.js"
|
||||
],
|
||||
"sha1": "9e13feb870cbb69188d12cb6eec660e77b7d5a9a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5e1392cb969e1c9acce6efef41c9cdcbbcaf17f0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-statement.js": [
|
||||
"Replaced '100' with '10'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-statement.js"
|
||||
],
|
||||
"sha1": "5e1392cb969e1c9acce6efef41c9cdcbbcaf17f0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a4e59a211561d2ce6a4fd8b11e5d33f58081c08e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-statement.js": [
|
||||
"Replaced '10' with '100'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-statement.js"
|
||||
],
|
||||
"sha1": "a4e59a211561d2ce6a4fd8b11e5d33f58081c08e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f4e6128f181cc5b4c23281999b335c778bd1f7fd"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-statement.js": [
|
||||
"Deleted the 'i = 0, init(); i < 100; i++' for statement",
|
||||
"Deleted the 'i = 0, init(); i < 10; i++' for statement",
|
||||
"Added the 'i = 0, init(); i < 100; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-statement.js"
|
||||
],
|
||||
"sha1": "f4e6128f181cc5b4c23281999b335c778bd1f7fd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "632d9badd2c08f84c89e54022539df87012dc47d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-statement.js": [
|
||||
"Deleted the 'i = 0, init(); i < 10; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-statement.js"
|
||||
],
|
||||
"sha1": "632d9badd2c08f84c89e54022539df87012dc47d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1325ae795a1a334f3a0bc6ce17b7b1d62ff4696a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-statement.js": [
|
||||
"Deleted the 'i = 0, init(); i < 100; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-statement.js"
|
||||
],
|
||||
"sha1": "1325ae795a1a334f3a0bc6ce17b7b1d62ff4696a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6f17186b61d196c816fb294ce4cbc82afd93342f"
|
||||
}]
|
131
test/corpus/diff-summaries/javascript/function-call-args.json
Normal file
131
test/corpus/diff-summaries/javascript/function-call-args.json
Normal file
@ -0,0 +1,131 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-function-call-args-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call-args.js": [
|
||||
"Added the 'someFunction(1, \"string\", …, true)' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call-args.js"
|
||||
],
|
||||
"sha1": "18a76a9b126f1849934890e3d7fb7c7eda43e575",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "10348b9625241c661ccbd03a8726a9ebe73f6840"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-args-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call-args.js": [
|
||||
"Added the 'someFunction(1, \"otherString\", …, false)' function call",
|
||||
"Added the 'someFunction(1, \"string\", …, true)' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call-args.js"
|
||||
],
|
||||
"sha1": "10348b9625241c661ccbd03a8726a9ebe73f6840",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a0b544891fbf2ce3e01b3afebee82ff7246dcc69"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-args-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call-args.js": [
|
||||
"Replaced the \"otherString\" string with the \"string\" string in the someFunction(1, \"string\", …, true) function call",
|
||||
"Replaced the 'c' identifier with the 'a' identifier in the someFunction(1, \"string\", …, true) function call",
|
||||
"Replaced the 'b' identifier with the 'a' identifier in the console.log(a) method call",
|
||||
"Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call",
|
||||
"Replaced 'false' with 'true' in the someFunction(1, \"string\", …, true) function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call-args.js"
|
||||
],
|
||||
"sha1": "a0b544891fbf2ce3e01b3afebee82ff7246dcc69",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "825246b2d2173a0813666832fa499e6b9c278103"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-args-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call-args.js": [
|
||||
"Replaced the \"string\" string with the \"otherString\" string in the someFunction(1, \"otherString\", …, false) function call",
|
||||
"Deleted the 'a' identifier in the someFunction(1, \"otherString\", …, false) function call",
|
||||
"Added the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call",
|
||||
"Replaced the 'a' identifier with the 'b' identifier in the console.log(b) method call",
|
||||
"Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call",
|
||||
"Replaced 'true' with 'false' in the someFunction(1, \"otherString\", …, false) function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call-args.js"
|
||||
],
|
||||
"sha1": "825246b2d2173a0813666832fa499e6b9c278103",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c7a1f5a6f449f06ba4d4ad8bb0bfcefb715bee8d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-args-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call-args.js": [
|
||||
"Deleted the 'someFunction(1, \"otherString\", …, false)' function call",
|
||||
"Deleted the 'someFunction(1, \"string\", …, true)' function call",
|
||||
"Added the 'someFunction(1, \"otherString\", …, false)' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call-args.js"
|
||||
],
|
||||
"sha1": "c7a1f5a6f449f06ba4d4ad8bb0bfcefb715bee8d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e41652451efb76e9fe1d64182dace55028eca25b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-args-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call-args.js": [
|
||||
"Deleted the 'someFunction(1, \"string\", …, true)' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call-args.js"
|
||||
],
|
||||
"sha1": "e41652451efb76e9fe1d64182dace55028eca25b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d8f988ca64a1d1156209947890d749bf80198285"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-args-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call-args.js": [
|
||||
"Deleted the 'someFunction(1, \"otherString\", …, false)' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call-args.js"
|
||||
],
|
||||
"sha1": "d8f988ca64a1d1156209947890d749bf80198285",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5aeda8deeda74b0668f87cbacb00781fd065df66"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/function-call.json
Normal file
122
test/corpus/diff-summaries/javascript/function-call.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-function-call-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Added the 'someFunction(arg1, \"arg2\")' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "c65612605de8c1f239d5529a0761a1fbd88a5833",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1dbda92373fc6478b73f3c42f94a60a933532bc4"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Added the 'someFunction(arg1, \"arg3\")' function call",
|
||||
"Added the 'someFunction(arg1, \"arg2\")' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "1dbda92373fc6478b73f3c42f94a60a933532bc4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "61f5f5397656d4a6e53e6fea7bc34550e45aa67d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Replaced the \"arg3\" string with the \"arg2\" string in the someFunction(arg1, \"arg2\") function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "61f5f5397656d4a6e53e6fea7bc34550e45aa67d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "446d3647ca066635fdb08fe7526bfc6a16c448a0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Replaced the \"arg2\" string with the \"arg3\" string in the someFunction(arg1, \"arg3\") function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "446d3647ca066635fdb08fe7526bfc6a16c448a0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4328cf836dedba2cdad08e2035bf20dfad915ead"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Deleted the 'someFunction(arg1, \"arg3\")' function call",
|
||||
"Deleted the 'someFunction(arg1, \"arg2\")' function call",
|
||||
"Added the 'someFunction(arg1, \"arg3\")' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "4328cf836dedba2cdad08e2035bf20dfad915ead",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5a6784920fb6aedfe394a0e15e853875dc142a39"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Deleted the 'someFunction(arg1, \"arg2\")' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "5a6784920fb6aedfe394a0e15e853875dc142a39",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b61899b75cc72e237fbd93221dd241d8753d12e5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Deleted the 'someFunction(arg1, \"arg3\")' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "b61899b75cc72e237fbd93221dd241d8753d12e5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0537c7a62228a569aab3a20308a6b4e683c1e489"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/function.json
Normal file
122
test/corpus/diff-summaries/javascript/function.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Added an anonymous (arg1, arg2) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "95af18d8919ff9cfae6d2f0c604ed1a6ad724386",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5bb57cfab6527c2c1d8a0e14da24040421c2fb5e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Added an anonymous (arg1, arg2) function",
|
||||
"Added an anonymous (arg1, arg2) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "5bb57cfab6527c2c1d8a0e14da24040421c2fb5e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "50815f2c902881bb2bb0533960a48c1b792c99f9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Replaced the 'arg1' identifier with the 'arg2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "50815f2c902881bb2bb0533960a48c1b792c99f9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "09acc34d47b0bc06ffa5f82f4c5c6c4b7029e168"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Replaced the 'arg2' identifier with the 'arg1' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "09acc34d47b0bc06ffa5f82f4c5c6c4b7029e168",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "98025a1112a6c666e481b82490be1ca0560c4e89"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Deleted an anonymous (arg1, arg2) function",
|
||||
"Deleted an anonymous (arg1, arg2) function",
|
||||
"Added an anonymous (arg1, arg2) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "98025a1112a6c666e481b82490be1ca0560c4e89",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "91f26f2a8712fb8a71af5e3c6ce6370903b43727"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Deleted an anonymous (arg1, arg2) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "91f26f2a8712fb8a71af5e3c6ce6370903b43727",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d7e622a3090bff71e032d19d908f1ca79d9a6d9b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Deleted an anonymous (arg1, arg2) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "d7e622a3090bff71e032d19d908f1ca79d9a6d9b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "fa671e38d081b4d20788ab07afa49516b99d2a5f"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/generator-function.json
Normal file
122
test/corpus/diff-summaries/javascript/generator-function.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-generator-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Added the 'generateStuff' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "907b5c72373793066771c9e049b754b7508f457a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "76735cb4eb1cd6e7443621744a2dba2c3307c84a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-generator-function-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Added the 'generateNewStuff' function",
|
||||
"Added the 'generateStuff' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "76735cb4eb1cd6e7443621744a2dba2c3307c84a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ab11363b7988d0b8701ff9947e63542aff4bfc59"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-generator-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Replaced the 'generateNewStuff' identifier with the 'generateStuff' identifier in the generateStuff function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "ab11363b7988d0b8701ff9947e63542aff4bfc59",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "29d9ab35ebd7a660cb6cf4f8922ce476897115f0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-generator-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Replaced the 'generateStuff' identifier with the 'generateNewStuff' identifier in the generateNewStuff function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "29d9ab35ebd7a660cb6cf4f8922ce476897115f0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f7ed636c58a10ad0c2599286d900aa32dab6de84"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-generator-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Deleted the 'generateNewStuff' function",
|
||||
"Deleted the 'generateStuff' function",
|
||||
"Added the 'generateNewStuff' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "f7ed636c58a10ad0c2599286d900aa32dab6de84",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c14290e3876039d5554c876ec1baf691ea27d9f1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-generator-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Deleted the 'generateStuff' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "c14290e3876039d5554c876ec1baf691ea27d9f1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0b51402ced5dea069e07d8936c74081b021f6d1c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-generator-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Deleted the 'generateNewStuff' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "0b51402ced5dea069e07d8936c74081b021f6d1c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2f747231adcd75d055ddc8b98d276039d1b5a094"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/identifier.json
Normal file
122
test/corpus/diff-summaries/javascript/identifier.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-identifier-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Added the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "aab18e237ace91db31cea86a6c4c43aa094b446e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "fd4d19bc8ba9b24ad62d312ccccbd36784d461c1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Added the 'theVar2' identifier",
|
||||
"Added the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "fd4d19bc8ba9b24ad62d312ccccbd36784d461c1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "24eeb87fe06701d2cb3acd87b703bf64e753851b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Replaced the 'theVar2' identifier with the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "24eeb87fe06701d2cb3acd87b703bf64e753851b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3356de1e40fd9bd62fcc01d8434765f9c0b5d92c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Replaced the 'theVar' identifier with the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "3356de1e40fd9bd62fcc01d8434765f9c0b5d92c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "40dbce8228310c17373b48e369fb69bc8409fd44"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Deleted the 'theVar2' identifier",
|
||||
"Deleted the 'theVar' identifier",
|
||||
"Added the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "40dbce8228310c17373b48e369fb69bc8409fd44",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "99e8262330b4d53d0411590e0cfaaf9f427add77"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Deleted the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "99e8262330b4d53d0411590e0cfaaf9f427add77",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8844ed7324501b20f347dc6d12e2a93d9e562bd0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Deleted the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "8844ed7324501b20f347dc6d12e2a93d9e562bd0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3b9b65c95588743484ed01e7158e8a2991302686"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/if-else.json
Normal file
122
test/corpus/diff-summaries/javascript/if-else.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-if-else-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Added the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "bfae6e88638f5d666df985b1cf13188d68e9f8a8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c970023e9ca99aecbccd5ac8f39c6fa31ee5c3c2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-else-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Added the 'a' if statement",
|
||||
"Added the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "c970023e9ca99aecbccd5ac8f39c6fa31ee5c3c2",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e0f1bb18b003fff7dff0e67ab8d66925d4554b20"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-else-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Replaced the 'a' if statement with the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "e0f1bb18b003fff7dff0e67ab8d66925d4554b20",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b1c0924e7d8fa080432463373d9044d6730729ed"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-else-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Replaced the 'x' if statement with the 'a' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "b1c0924e7d8fa080432463373d9044d6730729ed",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "33dee05f4038c5eec772d62a68cf3faf4b30388b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-else-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Deleted the 'a' if statement",
|
||||
"Deleted the 'x' if statement",
|
||||
"Added the 'a' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "33dee05f4038c5eec772d62a68cf3faf4b30388b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "dc554678c1fd7e7c7f7ac7585e110e15fd710a78"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-else-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Deleted the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "dc554678c1fd7e7c7f7ac7585e110e15fd710a78",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "82b3d3280883a01a5547f3a69d3b091a0d7dd93a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-else-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Deleted the 'a' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "82b3d3280883a01a5547f3a69d3b091a0d7dd93a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4188720196d3437b1a745c6626692a903ba63b3b"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/if.json
Normal file
122
test/corpus/diff-summaries/javascript/if.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-if-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Added the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "d7abae0335395b7f7d670fac59e05dab96a7222a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0c823f22b237a1025075582eeca2142db9428e79"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Added the 'a.b' if statement",
|
||||
"Added the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "0c823f22b237a1025075582eeca2142db9428e79",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "028fd43456799cd597eb45eb0516594290a8b660"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Replaced the 'a.b' if statement with the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "028fd43456799cd597eb45eb0516594290a8b660",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5ca9322073e86d240d8c93abdec6eb554352deff"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Replaced the 'x' if statement with the 'a.b' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "5ca9322073e86d240d8c93abdec6eb554352deff",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "15baf94e81c9e8188362524dca92212d48ef0d11"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Deleted the 'a.b' if statement",
|
||||
"Deleted the 'x' if statement",
|
||||
"Added the 'a.b' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "15baf94e81c9e8188362524dca92212d48ef0d11",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "96731cb905b6216c26b9176990a2a9a06431fe46"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Deleted the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "96731cb905b6216c26b9176990a2a9a06431fe46",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2f6c2a638d86227b42925bd88a6bbd36e4d69942"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Deleted the 'a.b' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "2f6c2a638d86227b42925bd88a6bbd36e4d69942",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bfae6e88638f5d666df985b1cf13188d68e9f8a8"
|
||||
}]
|
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-math-assignment-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-assignment-operator.js": [
|
||||
"Added the 'x' math assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-assignment-operator.js"
|
||||
],
|
||||
"sha1": "921348c0db5c7371a9d154653925c2efbaf8826b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4f25f2e665d9f90c13bb491361f23451304b60fe"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-assignment-operator.js": [
|
||||
"Added the 'x' math assignment",
|
||||
"Added the 'x' math assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-assignment-operator.js"
|
||||
],
|
||||
"sha1": "4f25f2e665d9f90c13bb491361f23451304b60fe",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b2fd86e651e8c0a42adba4366d9e25b1bf7b3cfc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-assignment-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-assignment-operator.js": [
|
||||
"Replaced '2' with '1' in the x math assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-assignment-operator.js"
|
||||
],
|
||||
"sha1": "b2fd86e651e8c0a42adba4366d9e25b1bf7b3cfc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0caa50a1b22ab76aed0b3b4df8baa781d72ba25d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-assignment-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-assignment-operator.js": [
|
||||
"Replaced '1' with '2' in the x math assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-assignment-operator.js"
|
||||
],
|
||||
"sha1": "0caa50a1b22ab76aed0b3b4df8baa781d72ba25d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0a045e6817f33c52f264e147b8f155d61487c266"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-assignment-operator.js": [
|
||||
"Deleted the 'x' math assignment",
|
||||
"Deleted the 'x' math assignment",
|
||||
"Added the 'x' math assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-assignment-operator.js"
|
||||
],
|
||||
"sha1": "0a045e6817f33c52f264e147b8f155d61487c266",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "edf29a75ccae42a5bdea31a09b5832139246fa66"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-assignment-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-assignment-operator.js": [
|
||||
"Deleted the 'x' math assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-assignment-operator.js"
|
||||
],
|
||||
"sha1": "edf29a75ccae42a5bdea31a09b5832139246fa66",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ccbf7db1314213915e260974b4669a85ef9886cd"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-assignment-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-assignment-operator.js": [
|
||||
"Deleted the 'x' math assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-assignment-operator.js"
|
||||
],
|
||||
"sha1": "ccbf7db1314213915e260974b4669a85ef9886cd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d2af5ec3c3ad375060911e7ecab418524b362fb0"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/math-operator.json
Normal file
124
test/corpus/diff-summaries/javascript/math-operator.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-math-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-operator.js": [
|
||||
"Added the 'i + j * 3 - j % 5' math operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-operator.js"
|
||||
],
|
||||
"sha1": "5849813ca5290325ffe39d290e78a99104035304",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ec72f4310f1d740528e1cb8971f5a44c99368910"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-operator-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-operator.js": [
|
||||
"Added the 'i + j * 2 - j % 4' math operator",
|
||||
"Added the 'i + j * 3 - j % 5' math operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-operator.js"
|
||||
],
|
||||
"sha1": "ec72f4310f1d740528e1cb8971f5a44c99368910",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8f77eb6febc2faeff938106f1ee0b4fec83b1926"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-operator.js": [
|
||||
"Replaced '2' with '3'",
|
||||
"Replaced '4' with '5'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-operator.js"
|
||||
],
|
||||
"sha1": "8f77eb6febc2faeff938106f1ee0b4fec83b1926",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0b5738f94a12baf7bebf8be4a2b5258140263e61"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-operator.js": [
|
||||
"Replaced '3' with '2'",
|
||||
"Replaced '5' with '4'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-operator.js"
|
||||
],
|
||||
"sha1": "0b5738f94a12baf7bebf8be4a2b5258140263e61",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "863e0bcea05ed4eef22b43a21c650e809672b8fa"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-operator.js": [
|
||||
"Deleted the 'i + j * 2 - j % 4' math operator",
|
||||
"Deleted the 'i + j * 3 - j % 5' math operator",
|
||||
"Added the 'i + j * 2 - j % 4' math operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-operator.js"
|
||||
],
|
||||
"sha1": "863e0bcea05ed4eef22b43a21c650e809672b8fa",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7c1c70d45bf38755d8451ee7d5ae6c8ce1f29e61"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-operator.js": [
|
||||
"Deleted the 'i + j * 3 - j % 5' math operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-operator.js"
|
||||
],
|
||||
"sha1": "7c1c70d45bf38755d8451ee7d5ae6c8ce1f29e61",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c2a4bf1a1ee700292a059b3c02552d3534c1ab01"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-operator.js": [
|
||||
"Deleted the 'i + j * 2 - j % 4' math operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-operator.js"
|
||||
],
|
||||
"sha1": "c2a4bf1a1ee700292a059b3c02552d3534c1ab01",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "59296bb55e2a8b7e4618367d4a796b089c2da907"
|
||||
}]
|
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-member-access-assignment-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access-assignment.js": [
|
||||
"Added the 'y.x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access-assignment.js"
|
||||
],
|
||||
"sha1": "410d8b5edf1e9ab9fc842fe489424a7b03f57d1c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "33f10ef6b48ab1750c301ae9ec5801e2e1ac7bb0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-assignment-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access-assignment.js": [
|
||||
"Added the 'y.x' assignment",
|
||||
"Added the 'y.x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access-assignment.js"
|
||||
],
|
||||
"sha1": "33f10ef6b48ab1750c301ae9ec5801e2e1ac7bb0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1a66baf78f9ff509efee981032237f8a902f853f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-assignment-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access-assignment.js": [
|
||||
"Replaced '1' with '0' in an assignment to y.x"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access-assignment.js"
|
||||
],
|
||||
"sha1": "1a66baf78f9ff509efee981032237f8a902f853f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "56c8d4ed17245e95530483c20ff39178de132a27"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-assignment-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access-assignment.js": [
|
||||
"Replaced '0' with '1' in an assignment to y.x"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access-assignment.js"
|
||||
],
|
||||
"sha1": "56c8d4ed17245e95530483c20ff39178de132a27",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bdded1dcea4cbac1edcbac8fbc776a74023ac5e5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-assignment-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access-assignment.js": [
|
||||
"Deleted the 'y.x' assignment",
|
||||
"Deleted the 'y.x' assignment",
|
||||
"Added the 'y.x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access-assignment.js"
|
||||
],
|
||||
"sha1": "bdded1dcea4cbac1edcbac8fbc776a74023ac5e5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "135c30ec136738a0021672b8a2a26c42c0e14780"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-assignment-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access-assignment.js": [
|
||||
"Deleted the 'y.x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access-assignment.js"
|
||||
],
|
||||
"sha1": "135c30ec136738a0021672b8a2a26c42c0e14780",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8b159e8f827652230408f94a29a6e07d29d5a3ad"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-assignment-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access-assignment.js": [
|
||||
"Deleted the 'y.x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access-assignment.js"
|
||||
],
|
||||
"sha1": "8b159e8f827652230408f94a29a6e07d29d5a3ad",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "97557f6e2c5ca659902339f573aec1c7bc1bba6b"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/member-access.json
Normal file
122
test/corpus/diff-summaries/javascript/member-access.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-member-access-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Added the 'x.someProperty' member access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "35191e787bea194267476a5eb4a43dc525bd28c3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b12a0a36785c7f97392d9337e5abfadb477e02fe"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Added the 'x.someOtherProperty' member access",
|
||||
"Added the 'x.someProperty' member access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "b12a0a36785c7f97392d9337e5abfadb477e02fe",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8df61ed905ad8cc2b2348eaf38f00eac9066e52e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Replaced the 'someOtherProperty' identifier with the 'someProperty' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "8df61ed905ad8cc2b2348eaf38f00eac9066e52e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ba252fd4634053d03e48a65388df7e5d1bf2698c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Replaced the 'someProperty' identifier with the 'someOtherProperty' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "ba252fd4634053d03e48a65388df7e5d1bf2698c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f3c8693395f4b08106d825474a33688622f41b4b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Deleted the 'x.someOtherProperty' member access",
|
||||
"Deleted the 'x.someProperty' member access",
|
||||
"Added the 'x.someOtherProperty' member access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "f3c8693395f4b08106d825474a33688622f41b4b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f2abac915269d158ccd7c57c3d5af06e018b44fc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Deleted the 'x.someProperty' member access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "f2abac915269d158ccd7c57c3d5af06e018b44fc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0b3499864622cf2b092dc92e16628043d72c84e9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Deleted the 'x.someOtherProperty' member access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "0b3499864622cf2b092dc92e16628043d72c84e9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5798d58803038f4f8b339c71382da80ef0217925"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/method-call.json
Normal file
122
test/corpus/diff-summaries/javascript/method-call.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-method-call-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-call.js": [
|
||||
"Added the 'object.someMethod(arg1, \"arg2\")' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"method-call.js"
|
||||
],
|
||||
"sha1": "0537c7a62228a569aab3a20308a6b4e683c1e489",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d2bfc0740793186d9c7d80d2f5e5f1f232a3efd1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-method-call-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-call.js": [
|
||||
"Added the 'object.someMethod(arg1, \"arg3\")' method call",
|
||||
"Added the 'object.someMethod(arg1, \"arg2\")' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"method-call.js"
|
||||
],
|
||||
"sha1": "d2bfc0740793186d9c7d80d2f5e5f1f232a3efd1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "94b149a107c2b39beadc547f507b59396bc0dcfa"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-method-call-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-call.js": [
|
||||
"Replaced the \"arg3\" string with the \"arg2\" string in the object.someMethod(arg1, \"arg2\") method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"method-call.js"
|
||||
],
|
||||
"sha1": "94b149a107c2b39beadc547f507b59396bc0dcfa",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ef1ad9d2c278ab44f493090c97f8cada5754f669"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-method-call-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-call.js": [
|
||||
"Replaced the \"arg2\" string with the \"arg3\" string in the object.someMethod(arg1, \"arg3\") method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"method-call.js"
|
||||
],
|
||||
"sha1": "ef1ad9d2c278ab44f493090c97f8cada5754f669",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a833ecd0e1694236c8050306e39070a5a0a8eae4"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-method-call-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-call.js": [
|
||||
"Deleted the 'object.someMethod(arg1, \"arg3\")' method call",
|
||||
"Deleted the 'object.someMethod(arg1, \"arg2\")' method call",
|
||||
"Added the 'object.someMethod(arg1, \"arg3\")' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"method-call.js"
|
||||
],
|
||||
"sha1": "a833ecd0e1694236c8050306e39070a5a0a8eae4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a1a78cd3da360ac1beca9815849b20619d8a0a7a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-method-call-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-call.js": [
|
||||
"Deleted the 'object.someMethod(arg1, \"arg2\")' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"method-call.js"
|
||||
],
|
||||
"sha1": "a1a78cd3da360ac1beca9815849b20619d8a0a7a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "769ff2e5ab865fabc988023dbb02143a1d3a3cfc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-method-call-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-call.js": [
|
||||
"Deleted the 'object.someMethod(arg1, \"arg3\")' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"method-call.js"
|
||||
],
|
||||
"sha1": "769ff2e5ab865fabc988023dbb02143a1d3a3cfc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "18a76a9b126f1849934890e3d7fb7c7eda43e575"
|
||||
}]
|
130
test/corpus/diff-summaries/javascript/named-function.json
Normal file
130
test/corpus/diff-summaries/javascript/named-function.json
Normal file
@ -0,0 +1,130 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-named-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Added the 'myFunction' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "2f747231adcd75d055ddc8b98d276039d1b5a094",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "95c12dc72b251772f817fe9279440c37c5a85638"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-named-function-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Added the 'anotherFunction' function",
|
||||
"Added the 'myFunction' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "95c12dc72b251772f817fe9279440c37c5a85638",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "47b4934bdb04f55a694e21f35201a981c6124de5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-named-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Replaced the 'anotherFunction' identifier with the 'myFunction' identifier in the myFunction function",
|
||||
"Added the 'arg1' identifier in the myFunction function",
|
||||
"Added the 'arg2' identifier in the myFunction function",
|
||||
"Added the 'arg2' identifier in the myFunction function",
|
||||
"Deleted the 'false' return statement in the myFunction function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "47b4934bdb04f55a694e21f35201a981c6124de5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1a8525476fbea48b8a414ba7916620f2ac9fe5d9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-named-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Replaced the 'myFunction' identifier with the 'anotherFunction' identifier in the myFunction function",
|
||||
"Deleted the 'arg1' identifier in the myFunction function",
|
||||
"Deleted the 'arg2' identifier in the myFunction function",
|
||||
"Added the 'false' return statement in the myFunction function",
|
||||
"Deleted the 'arg2' identifier in the myFunction function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "1a8525476fbea48b8a414ba7916620f2ac9fe5d9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "23b98195e5ad0d28ce93c966b1a318183457dd23"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-named-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Deleted the 'anotherFunction' function",
|
||||
"Deleted the 'myFunction' function",
|
||||
"Added the 'anotherFunction' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "23b98195e5ad0d28ce93c966b1a318183457dd23",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1e24bf4a7f46014ebd6864d44b03f129671e3dfc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-named-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Deleted the 'myFunction' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "1e24bf4a7f46014ebd6864d44b03f129671e3dfc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7c920ed7d74184e32974d7977dcc5fe0c9d35ca3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-named-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Deleted the 'anotherFunction' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "7c920ed7d74184e32974d7977dcc5fe0c9d35ca3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "35191e787bea194267476a5eb4a43dc525bd28c3"
|
||||
}]
|
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-nested-do-while-in-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-do-while-in-function.js": [
|
||||
"Added the 'f' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-do-while-in-function.js"
|
||||
],
|
||||
"sha1": "5f0caac0c003c801c82f7c9e56a9f148aa084921",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1c011b9d40b75a103799c7d82a0e636110351f5b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-do-while-in-function-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-do-while-in-function.js": [
|
||||
"Added the 'f' function",
|
||||
"Added the 'f' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-do-while-in-function.js"
|
||||
],
|
||||
"sha1": "1c011b9d40b75a103799c7d82a0e636110351f5b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1525b189d2528f7cbe4756f8b613ea11c1de11a6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-do-while-in-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-do-while-in-function.js": [
|
||||
"Replaced the 'arg2' identifier with the 'arg1' identifier in the something(arg1) function call of the 'f' function",
|
||||
"Replaced the 'arg1' identifier with the 'arg2' identifier in the arg2 do/while statement of the 'f' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-do-while-in-function.js"
|
||||
],
|
||||
"sha1": "1525b189d2528f7cbe4756f8b613ea11c1de11a6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bb83be164494b707522cd2e4a6e3f4b1cfb0528d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-do-while-in-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-do-while-in-function.js": [
|
||||
"Replaced the 'arg1' identifier with the 'arg2' identifier in the something(arg2) function call of the 'f' function",
|
||||
"Replaced the 'arg2' identifier with the 'arg1' identifier in the arg1 do/while statement of the 'f' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-do-while-in-function.js"
|
||||
],
|
||||
"sha1": "bb83be164494b707522cd2e4a6e3f4b1cfb0528d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "972d8a054eed44281b7e2708e27204a06e1313cd"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-do-while-in-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-do-while-in-function.js": [
|
||||
"Deleted the 'f' function",
|
||||
"Deleted the 'f' function",
|
||||
"Added the 'f' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-do-while-in-function.js"
|
||||
],
|
||||
"sha1": "972d8a054eed44281b7e2708e27204a06e1313cd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7617c3dcd781961121b9f150af160d397e9a0e2f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-do-while-in-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-do-while-in-function.js": [
|
||||
"Deleted the 'f' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-do-while-in-function.js"
|
||||
],
|
||||
"sha1": "7617c3dcd781961121b9f150af160d397e9a0e2f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b6f538cb4037d49d9d6dd0a7cbfc3874175f0920"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-do-while-in-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-do-while-in-function.js": [
|
||||
"Deleted the 'f' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-do-while-in-function.js"
|
||||
],
|
||||
"sha1": "b6f538cb4037d49d9d6dd0a7cbfc3874175f0920",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4ec7dc112cd4ee7df857942392d9c0a9b1c73d25"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/nested-functions.json
Normal file
124
test/corpus/diff-summaries/javascript/nested-functions.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-nested-functions-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-functions.js": [
|
||||
"Added the 'parent' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-functions.js"
|
||||
],
|
||||
"sha1": "32b06c62f51ab2e697c248000f022a1d8dcda42f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6e7802c47309255a1436ce9f0b93915810a3d3a9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-functions-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-functions.js": [
|
||||
"Added the 'parent' function",
|
||||
"Added the 'parent' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-functions.js"
|
||||
],
|
||||
"sha1": "6e7802c47309255a1436ce9f0b93915810a3d3a9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5dfc23d5164bb1961131c71377dbe9411beba038"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-functions-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-functions.js": [
|
||||
"Replaced the 'arg1' identifier with the 'arg3' identifier in the console.log(arg3) method call of the 'child' function",
|
||||
"Replaced the 'arg2' identifier with the 'arg4' identifier in the console.log(arg4) method call of the 'child' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-functions.js"
|
||||
],
|
||||
"sha1": "5dfc23d5164bb1961131c71377dbe9411beba038",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "80ac9fb88fa926c78e726f3c961990d9bf24bcc0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-functions-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-functions.js": [
|
||||
"Replaced the 'arg3' identifier with the 'arg1' identifier in the console.log(arg1) method call of the 'child' function",
|
||||
"Replaced the 'arg4' identifier with the 'arg2' identifier in the console.log(arg2) method call of the 'child' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-functions.js"
|
||||
],
|
||||
"sha1": "80ac9fb88fa926c78e726f3c961990d9bf24bcc0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "112e5c3e8b571d65832db5e7cf1e9cd488034e89"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-functions-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-functions.js": [
|
||||
"Deleted the 'parent' function",
|
||||
"Deleted the 'parent' function",
|
||||
"Added the 'parent' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-functions.js"
|
||||
],
|
||||
"sha1": "112e5c3e8b571d65832db5e7cf1e9cd488034e89",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3c9d8eadbe5aff49b4a5b957b123b178db815fd3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-functions-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-functions.js": [
|
||||
"Deleted the 'parent' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-functions.js"
|
||||
],
|
||||
"sha1": "3c9d8eadbe5aff49b4a5b957b123b178db815fd3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e799ea13b51ab6f52a9ea4dda5b822fe4f915a82"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-nested-functions-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"nested-functions.js": [
|
||||
"Deleted the 'parent' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"nested-functions.js"
|
||||
],
|
||||
"sha1": "e799ea13b51ab6f52a9ea4dda5b822fe4f915a82",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "365c92f02ea0be34a31f77d20526cb16728446c5"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/null.json
Normal file
124
test/corpus/diff-summaries/javascript/null.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-null-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Added the 'null' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "ca4e79fc2b040829f27146696485cd7ee0c3799b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4da05262f30a1d51d5cb8c5da095b6e6f4c71d44"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Added the 'null' return statement",
|
||||
"Added the 'null' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "4da05262f30a1d51d5cb8c5da095b6e6f4c71d44",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b4f9a24377d5464ca38eb1c9ab37a536fd1ab1a6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Added the 'null' identifier",
|
||||
"Deleted the 'null' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "b4f9a24377d5464ca38eb1c9ab37a536fd1ab1a6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cbf192b9190d67e12bc8ce40fa3a67f1a7d049c5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Added the 'null' return statement",
|
||||
"Deleted the 'null' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "cbf192b9190d67e12bc8ce40fa3a67f1a7d049c5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bf3d381bf56611acda49657336b134d56adf7ca3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Deleted the 'null' return statement",
|
||||
"Deleted the 'null' identifier",
|
||||
"Added the 'null' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "bf3d381bf56611acda49657336b134d56adf7ca3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6172c83ccb7e363cf7c9c00806e6996e9e18cad1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Deleted the 'null' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "6172c83ccb7e363cf7c9c00806e6996e9e18cad1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9fc4baeccfb3fb6c038cf5efc4a0681e9c3aebff"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Deleted the 'null' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "9fc4baeccfb3fb6c038cf5efc4a0681e9c3aebff",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "fb9592e3bb2b83a7c277c240b74b3c506f4979ed"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/number.json
Normal file
122
test/corpus/diff-summaries/javascript/number.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-number-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Added '101'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "45d982332dc1dfb3ad8bb332d0b7c3c2c748fff3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "15e011219ec4d632a30c42bd6f1c4fc7972ea058"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Added '102'",
|
||||
"Added '101'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "15e011219ec4d632a30c42bd6f1c4fc7972ea058",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "323296074b3d7a7448b7f68cd069df599654c450"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Replaced '102' with '101'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "323296074b3d7a7448b7f68cd069df599654c450",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "13c52dc686323f3e4cba0f2bc2393d0543f99d63"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Replaced '101' with '102'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "13c52dc686323f3e4cba0f2bc2393d0543f99d63",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "752d660054b18731ffae45bec428f8f4901071d8"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Deleted '102'",
|
||||
"Deleted '101'",
|
||||
"Added '102'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "752d660054b18731ffae45bec428f8f4901071d8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bb8075447a55be3944df38c6ec410eba10917e71"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Deleted '101'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "bb8075447a55be3944df38c6ec410eba10917e71",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d2dfe23480732a42effe8933a2ad5736b503b531"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Deleted '102'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "d2dfe23480732a42effe8933a2ad5736b503b531",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b0665d174f7073b730432253122aad996e5d8107"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/object-with-methods.json
Normal file
122
test/corpus/diff-summaries/javascript/object-with-methods.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-objects-with-methods-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Added the '{ add }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "7451453939a71bed1ff4fdd7d49f1541b5250916",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "12110da4178a42b0cf7e23a288a67bb4fc836f7f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-objects-with-methods-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Added the '{ subtract }' object",
|
||||
"Added the '{ add }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "12110da4178a42b0cf7e23a288a67bb4fc836f7f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "27be86468793d9fb7d13a6037266d60dbf72796b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-objects-with-methods-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Replaced the 'subtract' identifier with the 'add' identifier in the add method"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "27be86468793d9fb7d13a6037266d60dbf72796b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4be0419ff54c3d540a5a640f240bd54eef319eb7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-objects-with-methods-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Replaced the 'add' identifier with the 'subtract' identifier in the subtract method"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "4be0419ff54c3d540a5a640f240bd54eef319eb7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "82b8d9898da0aa6cb1f9c29f8284e1fd55dd6e4e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-objects-with-methods-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Deleted the '{ subtract }' object",
|
||||
"Deleted the '{ add }' object",
|
||||
"Added the '{ subtract }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "82b8d9898da0aa6cb1f9c29f8284e1fd55dd6e4e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "84044bf9e5e183457cd7941fb531f14de2fb1eb5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-objects-with-methods-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Deleted the '{ add }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "84044bf9e5e183457cd7941fb531f14de2fb1eb5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "220fbff125f89c24de08fb1bfaadd0c663c88ae3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-objects-with-methods-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Deleted the '{ subtract }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "220fbff125f89c24de08fb1bfaadd0c663c88ae3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "52cffc4738bafd83771b7e1718db8a6798f5fa29"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/object.json
Normal file
124
test/corpus/diff-summaries/javascript/object.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-object-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Added the '{ \"key1\": … }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "24eca334c726f2dafd54dc80fe297b19d5b49e0c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "eab2a7228b4674113a9b4808bf907d080fdc81fc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-object-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object",
|
||||
"Added the '{ \"key1\": … }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "eab2a7228b4674113a9b4808bf907d080fdc81fc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3f7f83fbfa36e6774a39b10cfedb6b7438682046"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-object-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Deleted the '\"key2\": …' pair",
|
||||
"Deleted the '\"key3\": …' pair"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "3f7f83fbfa36e6774a39b10cfedb6b7438682046",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b337130542f30ebd9d02c12334d2bbd08e548673"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-object-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Added the '\"key2\": …' pair",
|
||||
"Added the '\"key3\": …' pair"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "b337130542f30ebd9d02c12334d2bbd08e548673",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "eab6f47fe18108e84400a59b1f488df8f808dccd"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-object-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object",
|
||||
"Deleted the '{ \"key1\": … }' object",
|
||||
"Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "eab6f47fe18108e84400a59b1f488df8f808dccd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ce8a29dbc4f2e539e742e100c17baab8b69934db"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-object-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Deleted the '{ \"key1\": … }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "ce8a29dbc4f2e539e742e100c17baab8b69934db",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "32f565cb6c807539d665f1dcce7f89d569a4f9ea"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-object-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "32f565cb6c807539d665f1dcce7f89d569a4f9ea",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "682c9bc7b6e0bdf863dcaa32f63278a65cbae946"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/regex.json
Normal file
122
test/corpus/diff-summaries/javascript/regex.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-regex-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Added the '/one/g' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "86856e54b58a6f3766d716d6933999bd0465169e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ef57207785003c53cdf940ca41ff2e6f3797ab48"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-regex-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Added the '/on[^/]afe/gim' regex",
|
||||
"Added the '/one/g' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "ef57207785003c53cdf940ca41ff2e6f3797ab48",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "733217334461fe08348e702b749b01d626cf628a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-regex-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Replaced the '/on[^/]afe/gim' regex with the '/one/g' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "733217334461fe08348e702b749b01d626cf628a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4c1b595780648bd1f0c5a88fc1296c1fccc4e518"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-regex-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Replaced the '/one/g' regex with the '/on[^/]afe/gim' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "4c1b595780648bd1f0c5a88fc1296c1fccc4e518",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "02b258db4c9c0a27317de892a6a33316ea9e451d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-regex-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Deleted the '/on[^/]afe/gim' regex",
|
||||
"Deleted the '/one/g' regex",
|
||||
"Added the '/on[^/]afe/gim' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "02b258db4c9c0a27317de892a6a33316ea9e451d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "54f40aa957caab597fab4bcd6841535f9fbef1e8"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-regex-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Deleted the '/one/g' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "54f40aa957caab597fab4bcd6841535f9fbef1e8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0594c38cd32c35a0eaa7b6bf5588f44c879fa1d9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-regex-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Deleted the '/on[^/]afe/gim' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "0594c38cd32c35a0eaa7b6bf5588f44c879fa1d9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d7abae0335395b7f7d670fac59e05dab96a7222a"
|
||||
}]
|
112
test/corpus/diff-summaries/javascript/relational-operator.json
Normal file
112
test/corpus/diff-summaries/javascript/relational-operator.json
Normal file
@ -0,0 +1,112 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-relational-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"relational-operator.js": [
|
||||
"Added the 'x < y' relational operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"relational-operator.js"
|
||||
],
|
||||
"sha1": "734a1520f6190913ebe3373ef3eaea2eb8fa32ac",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "43884ef6050c6f827d907977c8c6d69f36b60b08"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-relational-operator-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"relational-operator.js": [
|
||||
"Added the 'x <= y' relational operator",
|
||||
"Added the 'x < y' relational operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"relational-operator.js"
|
||||
],
|
||||
"sha1": "43884ef6050c6f827d907977c8c6d69f36b60b08",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "28f0f2124c28153545bc86bcc7c0dd5628172918"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-relational-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"relational-operator.js"
|
||||
],
|
||||
"sha1": "28f0f2124c28153545bc86bcc7c0dd5628172918",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "667073573cdf74eff9977029a5a61d8915a9b087"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-relational-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"relational-operator.js"
|
||||
],
|
||||
"sha1": "667073573cdf74eff9977029a5a61d8915a9b087",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cf6efc4eb2be5b9ed67e5b478b30efed866742e2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-relational-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"relational-operator.js": [
|
||||
"Deleted the 'x <= y' relational operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"relational-operator.js"
|
||||
],
|
||||
"sha1": "cf6efc4eb2be5b9ed67e5b478b30efed866742e2",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "66c09163dfdf8668f37b0b47d961684102073b96"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-relational-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"relational-operator.js": [
|
||||
"Deleted the 'x < y' relational operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"relational-operator.js"
|
||||
],
|
||||
"sha1": "66c09163dfdf8668f37b0b47d961684102073b96",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "21d16c72332fc1be2daa9df1929207ab84facbe7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-relational-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"relational-operator.js": [
|
||||
"Deleted the 'x <= y' relational operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"relational-operator.js"
|
||||
],
|
||||
"sha1": "21d16c72332fc1be2daa9df1929207ab84facbe7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2d85e84d4e6eb6192b5094b6934b9a76e854325b"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/return-statement.json
Normal file
122
test/corpus/diff-summaries/javascript/return-statement.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-return-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Added the '5' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "b36aa3066096eea1f721208040f74bc7cf9a3c9e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2d6ae7a3e4cf4ac453028172ab43c0972962349a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-return-statement-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Added the 'empty' return statement",
|
||||
"Added the '5' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "2d6ae7a3e4cf4ac453028172ab43c0972962349a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "fea108b7711b2ac7e9529b66095ccd8954d4ebb9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-return-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Added '5'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "fea108b7711b2ac7e9529b66095ccd8954d4ebb9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "15ee9363230ed17b62dd10311721436a0ae61b60"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-return-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Deleted '5'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "15ee9363230ed17b62dd10311721436a0ae61b60",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f187b68543057279e9563a1bf472b3171f372ea3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-return-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Deleted the 'empty' return statement",
|
||||
"Deleted the '5' return statement",
|
||||
"Added the 'empty' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "f187b68543057279e9563a1bf472b3171f372ea3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "54d03de6792762a085f460012ca64599fcb3b2f9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-return-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Deleted the '5' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "54d03de6792762a085f460012ca64599fcb3b2f9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3eb1726ad9459097c9a74c3343805aae3effafb5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-return-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Deleted the 'empty' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "3eb1726ad9459097c9a74c3343805aae3effafb5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6632dc9f20866349fbee9cca32096a38d676fd99"
|
||||
}]
|
125
test/corpus/diff-summaries/javascript/string.json
Normal file
125
test/corpus/diff-summaries/javascript/string.json
Normal file
@ -0,0 +1,125 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-string-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {},
|
||||
"errors": {
|
||||
"string.js": [
|
||||
"Added the 'A string with \"double\" quotes' at line 0, column 0 - line 0, column 29 in string.js"
|
||||
]
|
||||
}
|
||||
},
|
||||
"filePaths": [
|
||||
"string.js"
|
||||
],
|
||||
"sha1": "52cffc4738bafd83771b7e1718db8a6798f5fa29",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9dc8b9dd30a6ba6ce0853873a534474eb96d106a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-string-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {},
|
||||
"errors": {
|
||||
"string.js": [
|
||||
"Added the 'A different string with \"double\" quotes' at line 0, column 0 - line 0, column 39 in string.js",
|
||||
"Replaced the 'A string with \"double\" quotes' at line 0, column 0 - line 0, column 29 in string.js with the 'A string with \"double\" quotes' at line 1, column 0 - line 1, column 29 in string.js",
|
||||
"Added the 'A string with \"double\" quotes' at line 2, column 0 - line 2, column 29 in string.js"
|
||||
]
|
||||
}
|
||||
},
|
||||
"filePaths": [
|
||||
"string.js"
|
||||
],
|
||||
"sha1": "9dc8b9dd30a6ba6ce0853873a534474eb96d106a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6bfd49ecc281ae186167137d2ed6fb931a016157"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-string-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {},
|
||||
"errors": {
|
||||
"string.js": [
|
||||
"Replaced the 'A different string with \"double\" quotes' at line 0, column 0 - line 0, column 39 in string.js with the 'A string with \"double\" quotes' at line 0, column 0 - line 0, column 29 in string.js"
|
||||
]
|
||||
}
|
||||
},
|
||||
"filePaths": [
|
||||
"string.js"
|
||||
],
|
||||
"sha1": "6bfd49ecc281ae186167137d2ed6fb931a016157",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3028c671c5acbf6352027a268095da7b1eb5165a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-string-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {},
|
||||
"errors": {
|
||||
"string.js": [
|
||||
"Replaced the 'A string with \"double\" quotes' at line 0, column 0 - line 0, column 29 in string.js with the 'A different string with \"double\" quotes' at line 0, column 0 - line 0, column 39 in string.js"
|
||||
]
|
||||
}
|
||||
},
|
||||
"filePaths": [
|
||||
"string.js"
|
||||
],
|
||||
"sha1": "3028c671c5acbf6352027a268095da7b1eb5165a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "86ad5f2e84004a96ef8cbf1e6ba37d1a6e31b314"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-string-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {},
|
||||
"errors": {
|
||||
"string.js": [
|
||||
"Added the 'A string with \"double\" quotes' at line 0, column 0 - line 0, column 29 in string.js",
|
||||
"Replaced the 'A different string with \"double\" quotes' at line 0, column 0 - line 0, column 39 in string.js with the 'A different string with \"double\" quotes' at line 1, column 0 - line 1, column 39 in string.js",
|
||||
"Deleted the 'A string with \"double\" quotes' at line 1, column 0 - line 1, column 29 in string.js",
|
||||
"Deleted the 'A string with \"double\" quotes' at line 2, column 0 - line 2, column 29 in string.js"
|
||||
]
|
||||
}
|
||||
},
|
||||
"filePaths": [
|
||||
"string.js"
|
||||
],
|
||||
"sha1": "86ad5f2e84004a96ef8cbf1e6ba37d1a6e31b314",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c8b7d4fcb77341fa1af307226699de3449647703"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-string-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {},
|
||||
"errors": {
|
||||
"string.js": [
|
||||
"Replaced the 'A string with \"double\" quotes' at line 0, column 0 - line 0, column 29 in string.js with the 'A different string with \"double\" quotes' at line 0, column 0 - line 0, column 39 in string.js",
|
||||
"Deleted the 'A different string with \"double\" quotes' at line 1, column 0 - line 1, column 39 in string.js"
|
||||
]
|
||||
}
|
||||
},
|
||||
"filePaths": [
|
||||
"string.js"
|
||||
],
|
||||
"sha1": "c8b7d4fcb77341fa1af307226699de3449647703",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "56b7084844f28b1347693f385a7282214f50cc23"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-string-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {},
|
||||
"errors": {
|
||||
"string.js": [
|
||||
"Deleted the 'A different string with \"double\" quotes' at line 0, column 0 - line 0, column 39 in string.js"
|
||||
]
|
||||
}
|
||||
},
|
||||
"filePaths": [
|
||||
"string.js"
|
||||
],
|
||||
"sha1": "56b7084844f28b1347693f385a7282214f50cc23",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "45d982332dc1dfb3ad8bb332d0b7c3c2c748fff3"
|
||||
}]
|
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-subscript-access-assignment-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-assignment.js": [
|
||||
"Added the 'y[\"x\"]' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-assignment.js"
|
||||
],
|
||||
"sha1": "97557f6e2c5ca659902339f573aec1c7bc1bba6b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "20c864ac24291353ea7ad649ad665c15a63bd446"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-assignment.js": [
|
||||
"Added the 'y[\"x\"]' assignment",
|
||||
"Added the 'y[\"x\"]' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-assignment.js"
|
||||
],
|
||||
"sha1": "20c864ac24291353ea7ad649ad665c15a63bd446",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "140b7be5da826477e10c82a0f4852817981884f9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-assignment.js": [
|
||||
"Replaced '1' with '0' in an assignment to y[\"x\"]"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-assignment.js"
|
||||
],
|
||||
"sha1": "140b7be5da826477e10c82a0f4852817981884f9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d1b0a022337317757b9b6e9b8a1b3a2630964dce"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-assignment-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-assignment.js": [
|
||||
"Replaced '0' with '1' in an assignment to y[\"x\"]"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-assignment.js"
|
||||
],
|
||||
"sha1": "d1b0a022337317757b9b6e9b8a1b3a2630964dce",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "29f4185973858cde2c30ba1e67be201edb295b70"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-assignment.js": [
|
||||
"Deleted the 'y[\"x\"]' assignment",
|
||||
"Deleted the 'y[\"x\"]' assignment",
|
||||
"Added the 'y[\"x\"]' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-assignment.js"
|
||||
],
|
||||
"sha1": "29f4185973858cde2c30ba1e67be201edb295b70",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "686c33ab583882ea30b05f41ad0a4793bb19e24e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-assignment-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-assignment.js": [
|
||||
"Deleted the 'y[\"x\"]' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-assignment.js"
|
||||
],
|
||||
"sha1": "686c33ab583882ea30b05f41ad0a4793bb19e24e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f759fa69ff1b8b2f9be480d923e9c25dbdba62eb"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-assignment.js": [
|
||||
"Deleted the 'y[\"x\"]' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-assignment.js"
|
||||
],
|
||||
"sha1": "f759fa69ff1b8b2f9be480d923e9c25dbdba62eb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5ed18af6b663f85d2635954f1488222c50b359d8"
|
||||
}]
|
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-subscript-access-string-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-string.js": [
|
||||
"Added the 'x[\"some-string\"]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-string.js"
|
||||
],
|
||||
"sha1": "818ac5b0ae1ee327fa800a38cb86b1943b95426d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f95ec1098eba2db8417ebc9bcd2e241696d24561"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-string-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-string.js": [
|
||||
"Added the 'x[\"some-other-string\"]' subscript access",
|
||||
"Added the 'x[\"some-string\"]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-string.js"
|
||||
],
|
||||
"sha1": "f95ec1098eba2db8417ebc9bcd2e241696d24561",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4867184725c500cb960db3caa18e34f45d827183"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-string-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-string.js": [
|
||||
"Replaced the \"some-other-string\" string with the \"some-string\" string in the x[\"some-string\"] subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-string.js"
|
||||
],
|
||||
"sha1": "4867184725c500cb960db3caa18e34f45d827183",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "97831e9b2ee3bdbd54dbffd3dd682575f1866029"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-string-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-string.js": [
|
||||
"Replaced the \"some-string\" string with the \"some-other-string\" string in the x[\"some-other-string\"] subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-string.js"
|
||||
],
|
||||
"sha1": "97831e9b2ee3bdbd54dbffd3dd682575f1866029",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "882eb108ca6216b04d3dcdb5fa9e8fb9a66869bc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-string-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-string.js": [
|
||||
"Deleted the 'x[\"some-other-string\"]' subscript access",
|
||||
"Deleted the 'x[\"some-string\"]' subscript access",
|
||||
"Added the 'x[\"some-other-string\"]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-string.js"
|
||||
],
|
||||
"sha1": "882eb108ca6216b04d3dcdb5fa9e8fb9a66869bc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "aec5cca9776e6b4fd0b2edadf63d6ca5b1e825b7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-string-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-string.js": [
|
||||
"Deleted the 'x[\"some-string\"]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-string.js"
|
||||
],
|
||||
"sha1": "aec5cca9776e6b4fd0b2edadf63d6ca5b1e825b7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "826953e83bae8b879673210442db329beb060a25"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-string-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-string.js": [
|
||||
"Deleted the 'x[\"some-other-string\"]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-string.js"
|
||||
],
|
||||
"sha1": "826953e83bae8b879673210442db329beb060a25",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2af71438d83e47601320a632ea6bc26ae90a70d8"
|
||||
}]
|
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-subscript-access-variable-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-variable.js": [
|
||||
"Added the 'x[someVariable]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-variable.js"
|
||||
],
|
||||
"sha1": "5798d58803038f4f8b339c71382da80ef0217925",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "beca23714191b0aaf5b5a1045f67f63422e30506"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-variable-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-variable.js": [
|
||||
"Added the 'x[someOtherVariable]' subscript access",
|
||||
"Added the 'x[someVariable]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-variable.js"
|
||||
],
|
||||
"sha1": "beca23714191b0aaf5b5a1045f67f63422e30506",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3fe2accf4868e1fa807b18ba36ffcbfb8b89c5d3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-variable-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-variable.js": [
|
||||
"Replaced the 'someOtherVariable' identifier with the 'someVariable' identifier in the x[someVariable] subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-variable.js"
|
||||
],
|
||||
"sha1": "3fe2accf4868e1fa807b18ba36ffcbfb8b89c5d3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6ec0dd79b7a1f17acf2098be3d62f6df341930b0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-variable-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-variable.js": [
|
||||
"Replaced the 'someVariable' identifier with the 'someOtherVariable' identifier in the x[someOtherVariable] subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-variable.js"
|
||||
],
|
||||
"sha1": "6ec0dd79b7a1f17acf2098be3d62f6df341930b0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1ebab00124482446ea3dab401414dbd92a79f9c0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-variable.js": [
|
||||
"Deleted the 'x[someOtherVariable]' subscript access",
|
||||
"Deleted the 'x[someVariable]' subscript access",
|
||||
"Added the 'x[someOtherVariable]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-variable.js"
|
||||
],
|
||||
"sha1": "1ebab00124482446ea3dab401414dbd92a79f9c0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "15d8b4425517d34197b111c66da6f2d07d7c100a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-variable-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-variable.js": [
|
||||
"Deleted the 'x[someVariable]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-variable.js"
|
||||
],
|
||||
"sha1": "15d8b4425517d34197b111c66da6f2d07d7c100a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a0ac736713f16ba00f1b4a4862fa440a5caca4af"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-variable-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-variable.js": [
|
||||
"Deleted the 'x[someOtherVariable]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-variable.js"
|
||||
],
|
||||
"sha1": "a0ac736713f16ba00f1b4a4862fa440a5caca4af",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "818ac5b0ae1ee327fa800a38cb86b1943b95426d"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/switch-statement.json
Normal file
124
test/corpus/diff-summaries/javascript/switch-statement.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-switch-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Added the '1' switch statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "e744226ef998687c390e01091951dba025d40dfd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bc7468ae016de58406ed2d8bdbb977fe5027bdc7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-switch-statement-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Added the '2' switch statement",
|
||||
"Added the '1' switch statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "bc7468ae016de58406ed2d8bdbb977fe5027bdc7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0c65e7794f6a6601e8418869d707e9945b6dfb3a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-switch-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Replaced '2' with '1'",
|
||||
"Replaced '2' with '1'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "0c65e7794f6a6601e8418869d707e9945b6dfb3a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "04e07392b9bc9e3674217cb3ac322ecf6fcf71d7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-switch-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Replaced '1' with '2'",
|
||||
"Replaced '1' with '2'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "04e07392b9bc9e3674217cb3ac322ecf6fcf71d7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a61fe4d85bd88a2ec93c6a74d741aae3c6ef4d97"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-switch-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Deleted the '2' switch statement",
|
||||
"Deleted the '1' switch statement",
|
||||
"Added the '2' switch statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "a61fe4d85bd88a2ec93c6a74d741aae3c6ef4d97",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1eb32b98fc86b9304b04fdc7f68cb6fc80cdda9e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-switch-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Deleted the '1' switch statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "1eb32b98fc86b9304b04fdc7f68cb6fc80cdda9e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ed5407f7d0670c5455d3c8dcb9907aee676c19d7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-switch-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Deleted the '2' switch statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "ed5407f7d0670c5455d3c8dcb9907aee676c19d7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0ba23e1269b5b38e6ec69120b738ff7c825beeca"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/template-string.json
Normal file
122
test/corpus/diff-summaries/javascript/template-string.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-template-string-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"template-string.js": [
|
||||
"Added the '`one line`' template string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"template-string.js"
|
||||
],
|
||||
"sha1": "4188720196d3437b1a745c6626692a903ba63b3b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0afc56f69a9f501bff6a163ef287acd6e5cc6017"
|
||||
}
|
||||
,{
|
||||
"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": "0afc56f69a9f501bff6a163ef287acd6e5cc6017",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "779225b6216f83ca9bee4c7edafe0cc93e399c12"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-template-string-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"template-string.js": [
|
||||
"Replaced the '`multi line`' template string with the '`one line`' template string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"template-string.js"
|
||||
],
|
||||
"sha1": "779225b6216f83ca9bee4c7edafe0cc93e399c12",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ba16139069f94c58a140abef4a899b591097809b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-template-string-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"template-string.js": [
|
||||
"Replaced the '`one line`' template string with the '`multi line`' template string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"template-string.js"
|
||||
],
|
||||
"sha1": "ba16139069f94c58a140abef4a899b591097809b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d48d2ae27005bb939d502c8b8adeaadaeeef2e29"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-template-string-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"template-string.js": [
|
||||
"Deleted the '`multi line`' template string",
|
||||
"Deleted the '`one line`' template string",
|
||||
"Added the '`multi line`' template string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"template-string.js"
|
||||
],
|
||||
"sha1": "d48d2ae27005bb939d502c8b8adeaadaeeef2e29",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "94133f22ddd0d83521dfcf914906d375a2d39495"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-template-string-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"template-string.js": [
|
||||
"Deleted the '`one line`' template string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"template-string.js"
|
||||
],
|
||||
"sha1": "94133f22ddd0d83521dfcf914906d375a2d39495",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "83f7aee7416d2e8434af935fdb2409e946d1569a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-template-string-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"template-string.js": [
|
||||
"Deleted the '`multi line`' template string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"template-string.js"
|
||||
],
|
||||
"sha1": "83f7aee7416d2e8434af935fdb2409e946d1569a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ea2df743568a320252df57e60055d8d6e611d9e7"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/ternary.json
Normal file
124
test/corpus/diff-summaries/javascript/ternary.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-ternary-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"ternary.js": [
|
||||
"Added the 'condition' ternary expression"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"ternary.js"
|
||||
],
|
||||
"sha1": "6f2be827ecaee324c13a7571522397d699609382",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ffeb9c1c9867caf527dd78dbb18ddfa17ba347c8"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-ternary-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"ternary.js": [
|
||||
"Added the 'x.y' assignment",
|
||||
"Added the 'condition' ternary expression"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"ternary.js"
|
||||
],
|
||||
"sha1": "ffeb9c1c9867caf527dd78dbb18ddfa17ba347c8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d3f99f9adefa2855bfff79b506875cdb00dd5f81"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-ternary-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"ternary.js": [
|
||||
"Added the 'condition' ternary expression",
|
||||
"Deleted the 'x.y' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"ternary.js"
|
||||
],
|
||||
"sha1": "d3f99f9adefa2855bfff79b506875cdb00dd5f81",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5e6d34a0008ac45770ef5f5ed5a13b9c26732437"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-ternary-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"ternary.js": [
|
||||
"Added the 'x.y' assignment",
|
||||
"Deleted the 'condition' ternary expression"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"ternary.js"
|
||||
],
|
||||
"sha1": "5e6d34a0008ac45770ef5f5ed5a13b9c26732437",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d3661843068779ae99558ca3993a93d664bd47be"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-ternary-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"ternary.js": [
|
||||
"Deleted the 'x.y' assignment",
|
||||
"Deleted the 'condition' ternary expression",
|
||||
"Added the 'x.y' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"ternary.js"
|
||||
],
|
||||
"sha1": "d3661843068779ae99558ca3993a93d664bd47be",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "aac9a05c1262172adc916dbc3598f5d1b8affa10"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-ternary-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"ternary.js": [
|
||||
"Deleted the 'condition' ternary expression"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"ternary.js"
|
||||
],
|
||||
"sha1": "aac9a05c1262172adc916dbc3598f5d1b8affa10",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1693184ae80d84e025267dcdb4e5c5b732364b0b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-ternary-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"ternary.js": [
|
||||
"Deleted the 'x.y' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"ternary.js"
|
||||
],
|
||||
"sha1": "1693184ae80d84e025267dcdb4e5c5b732364b0b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c218fb3f04f316af4d3665e071ab85f4245435f4"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/this-expression.json
Normal file
124
test/corpus/diff-summaries/javascript/this-expression.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-this-expression-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"this-expression.js": [
|
||||
"Added the 'this' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"this-expression.js"
|
||||
],
|
||||
"sha1": "3b9b65c95588743484ed01e7158e8a2991302686",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a7227bd4b634e69fac1fab2cff7af9402fbd4690"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-this-expression-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"this-expression.js": [
|
||||
"Added the 'this' return statement",
|
||||
"Added the 'this' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"this-expression.js"
|
||||
],
|
||||
"sha1": "a7227bd4b634e69fac1fab2cff7af9402fbd4690",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0e96ad1e49a64063fb7ba060cd016b8e5f6ab504"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-this-expression-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"this-expression.js": [
|
||||
"Added the 'this' identifier",
|
||||
"Deleted the 'this' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"this-expression.js"
|
||||
],
|
||||
"sha1": "0e96ad1e49a64063fb7ba060cd016b8e5f6ab504",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b2f960d60e3967745c4c1e86852958d4f37bba7f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-this-expression-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"this-expression.js": [
|
||||
"Added the 'this' return statement",
|
||||
"Deleted the 'this' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"this-expression.js"
|
||||
],
|
||||
"sha1": "b2f960d60e3967745c4c1e86852958d4f37bba7f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "361381620f7134f044c141dc3b3c08dc7eca63d9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-this-expression-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"this-expression.js": [
|
||||
"Deleted the 'this' return statement",
|
||||
"Deleted the 'this' identifier",
|
||||
"Added the 'this' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"this-expression.js"
|
||||
],
|
||||
"sha1": "361381620f7134f044c141dc3b3c08dc7eca63d9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "076b140acac2aef55ee756d6ecd8a754bb08f15e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-this-expression-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"this-expression.js": [
|
||||
"Deleted the 'this' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"this-expression.js"
|
||||
],
|
||||
"sha1": "076b140acac2aef55ee756d6ecd8a754bb08f15e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6a794599dcbb5afeac02b013ee56958c02749a12"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-this-expression-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"this-expression.js": [
|
||||
"Deleted the 'this' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"this-expression.js"
|
||||
],
|
||||
"sha1": "6a794599dcbb5afeac02b013ee56958c02749a12",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ca4e79fc2b040829f27146696485cd7ee0c3799b"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/throw-statement.json
Normal file
122
test/corpus/diff-summaries/javascript/throw-statement.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-throw-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"throw-statement.js": [
|
||||
"Added the 'new Error(\"uh oh\")' throw statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"throw-statement.js"
|
||||
],
|
||||
"sha1": "0ba23e1269b5b38e6ec69120b738ff7c825beeca",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "be8b977c8408358a831d40ac8cff3edad5c84dfd"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-throw-statement-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"throw-statement.js": [
|
||||
"Added the 'new Error(\"oooooops\")' throw statement",
|
||||
"Added the 'new Error(\"uh oh\")' throw statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"throw-statement.js"
|
||||
],
|
||||
"sha1": "be8b977c8408358a831d40ac8cff3edad5c84dfd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ce38322f89e0b45dc38bd23f03e307bc4516ef3b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-throw-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"throw-statement.js": [
|
||||
"Replaced the \"oooooops\" string with the \"uh oh\" string in the Error(\"uh oh\") function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"throw-statement.js"
|
||||
],
|
||||
"sha1": "ce38322f89e0b45dc38bd23f03e307bc4516ef3b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a2d831628f3b08fef8fb03855768e353cc4c512f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-throw-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"throw-statement.js": [
|
||||
"Replaced the \"uh oh\" string with the \"oooooops\" string in the Error(\"oooooops\") function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"throw-statement.js"
|
||||
],
|
||||
"sha1": "a2d831628f3b08fef8fb03855768e353cc4c512f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "40d94d43115d5f2b634758701a4dd4f55dcd09a3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-throw-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"throw-statement.js": [
|
||||
"Deleted the 'new Error(\"oooooops\")' throw statement",
|
||||
"Deleted the 'new Error(\"uh oh\")' throw statement",
|
||||
"Added the 'new Error(\"oooooops\")' throw statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"throw-statement.js"
|
||||
],
|
||||
"sha1": "40d94d43115d5f2b634758701a4dd4f55dcd09a3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0531ad3a5aefaed3e6a0da9625edf1d93885c344"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-throw-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"throw-statement.js": [
|
||||
"Deleted the 'new Error(\"uh oh\")' throw statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"throw-statement.js"
|
||||
],
|
||||
"sha1": "0531ad3a5aefaed3e6a0da9625edf1d93885c344",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d49c0496db9be00a42e35a493313718e241bd721"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-throw-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"throw-statement.js": [
|
||||
"Deleted the 'new Error(\"oooooops\")' throw statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"throw-statement.js"
|
||||
],
|
||||
"sha1": "d49c0496db9be00a42e35a493313718e241bd721",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6a2cc9557e1d0cc88ad1ead96d1f6c524a3cdcc4"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/true.json
Normal file
124
test/corpus/diff-summaries/javascript/true.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-true-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Added 'true'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "d28adf18a24eb20bc2caaeddf797caf5f924683c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7aa3c6c50f6053ae0bda71ca491c7ebe01031a56"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Added the 'true' return statement",
|
||||
"Added 'true'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "7aa3c6c50f6053ae0bda71ca491c7ebe01031a56",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c7c2780c17afab5630bac4d707b5d22d0db27381"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Added 'true'",
|
||||
"Deleted the 'true' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "c7c2780c17afab5630bac4d707b5d22d0db27381",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "69bf6e5d93f02d1d192d0f6ec0e7e7c22bab8725"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Added the 'true' return statement",
|
||||
"Deleted 'true'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "69bf6e5d93f02d1d192d0f6ec0e7e7c22bab8725",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3e525da36f8849b934c22591cd43d5e0768fe12b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Deleted the 'true' return statement",
|
||||
"Deleted 'true'",
|
||||
"Added the 'true' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "3e525da36f8849b934c22591cd43d5e0768fe12b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "967c20e9c86ea327c93f9df4169e8df0fb03fde3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Deleted 'true'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "967c20e9c86ea327c93f9df4169e8df0fb03fde3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1a8dccbecf2efd4038c1835b38564a3f3956a6cb"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Deleted the 'true' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "1a8dccbecf2efd4038c1835b38564a3f3956a6cb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1c81c54c83779f2e84d6c0820063f8b9def43147"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/try-statement.json
Normal file
124
test/corpus/diff-summaries/javascript/try-statement.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-try-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Added the '{ f; }' try statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "6a2cc9557e1d0cc88ad1ead96d1f6c524a3cdcc4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a12f2a1233c8978dbc99c5dc60418626ab496741"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-try-statement-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Added the '{ f; }' try statement",
|
||||
"Added the '{ f; }' try statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "a12f2a1233c8978dbc99c5dc60418626ab496741",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c7e256871fe17be3d2ab1025d8d159863ade87c7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-try-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Replaced the 'h' identifier with the 'g' identifier",
|
||||
"Replaced the 'g' identifier with the 'h' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "c7e256871fe17be3d2ab1025d8d159863ade87c7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "35c9003ee2fa8fce6bd979e0a2613fc36cf71d11"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-try-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Replaced the 'g' identifier with the 'h' identifier",
|
||||
"Replaced the 'h' identifier with the 'g' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "35c9003ee2fa8fce6bd979e0a2613fc36cf71d11",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6ceeada95359347cf660459df9c749c8884a3300"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-try-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Deleted the '{ f; }' try statement",
|
||||
"Deleted the '{ f; }' try statement",
|
||||
"Added the '{ f; }' try statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "6ceeada95359347cf660459df9c749c8884a3300",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9a11bac7e8ae5873b3db2460faa8a6b58006dc04"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-try-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Deleted the '{ f; }' try statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "9a11bac7e8ae5873b3db2460faa8a6b58006dc04",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e5c36c51ce11a14721011c8030fb692b1e26a363"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-try-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Deleted the '{ f; }' try statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "e5c36c51ce11a14721011c8030fb692b1e26a363",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "86856e54b58a6f3766d716d6933999bd0465169e"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/type-operator.json
Normal file
122
test/corpus/diff-summaries/javascript/type-operator.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-type-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Added the 'typeof x' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "c218fb3f04f316af4d3665e071ab85f4245435f4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f5d0b90491c3b05a28e5d681eb63374c9db49c1b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-type-operator-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Added the 'x instanceof String' operator",
|
||||
"Added the 'typeof x' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "f5d0b90491c3b05a28e5d681eb63374c9db49c1b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6883be2bee32b251a12d8a33a8299844a2b8a42f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-type-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Deleted the 'String' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "6883be2bee32b251a12d8a33a8299844a2b8a42f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "92defb442b6402d8d2e76c35f4bd418e25ce144e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-type-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Added the 'String' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "92defb442b6402d8d2e76c35f4bd418e25ce144e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "587b7cd1e5aeb711135a7838883347899697fb29"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-type-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Deleted the 'x instanceof String' operator",
|
||||
"Deleted the 'typeof x' operator",
|
||||
"Added the 'x instanceof String' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "587b7cd1e5aeb711135a7838883347899697fb29",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "495cd86b5854b952d1e02415ccf9f3716f526b3e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-type-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Deleted the 'typeof x' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "495cd86b5854b952d1e02415ccf9f3716f526b3e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4be2e12e3543a08a9dd1388790bf40e3ff137b21"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-type-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Deleted the 'x instanceof String' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "4be2e12e3543a08a9dd1388790bf40e3ff137b21",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e21de869506a2a72943755153b5a36862ef80f6c"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/undefined.json
Normal file
124
test/corpus/diff-summaries/javascript/undefined.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-undefined-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Added the 'undefined' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "fb9592e3bb2b83a7c277c240b74b3c506f4979ed",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f4f7e677d1b68fa8a7c5a113f0bc1229789843c9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Added the 'undefined' return statement",
|
||||
"Added the 'undefined' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "f4f7e677d1b68fa8a7c5a113f0bc1229789843c9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d2c9f0c30c17b2fae1f9aff068b96d77d2629002"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Added the 'undefined' identifier",
|
||||
"Deleted the 'undefined' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "d2c9f0c30c17b2fae1f9aff068b96d77d2629002",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ecc26983fb3905b5da582d38fe661405682fd79c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Added the 'undefined' return statement",
|
||||
"Deleted the 'undefined' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "ecc26983fb3905b5da582d38fe661405682fd79c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "02dd9718b4821f06a28527e58469f70b0cdd3007"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Deleted the 'undefined' return statement",
|
||||
"Deleted the 'undefined' identifier",
|
||||
"Added the 'undefined' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "02dd9718b4821f06a28527e58469f70b0cdd3007",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "001c05a19dce4903649e38680c7db3ffa9dca6ad"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Deleted the 'undefined' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "001c05a19dce4903649e38680c7db3ffa9dca6ad",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "64d634f1d7993d94a75c7e4aca355d26f55c75b7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Deleted the 'undefined' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "64d634f1d7993d94a75c7e4aca355d26f55c75b7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d28adf18a24eb20bc2caaeddf797caf5f924683c"
|
||||
}]
|
134
test/corpus/diff-summaries/javascript/var-declaration.json
Normal file
134
test/corpus/diff-summaries/javascript/var-declaration.json
Normal file
@ -0,0 +1,134 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-var-declaration-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Added the 'x' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "6632dc9f20866349fbee9cca32096a38d676fd99",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "68fbed5e0138cf9909be8249f5e56f4a601b105e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-var-declaration-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Added the 'x' variable",
|
||||
"Added the 'y' variable",
|
||||
"Added the 'z' variable",
|
||||
"Added the 'x' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "68fbed5e0138cf9909be8249f5e56f4a601b105e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a5bb584db7c76ad0fb098032dce44c6ab55068ca"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-var-declaration-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Replaced the 'x' variable with the 'x' variable",
|
||||
"Deleted the 'y' variable",
|
||||
"Deleted the 'z' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "a5bb584db7c76ad0fb098032dce44c6ab55068ca",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b1f0bb9999d84d984ba7d9445e6846c36257b748"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-var-declaration-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Replaced the 'x' variable with the 'x' variable",
|
||||
"Added the 'y' variable",
|
||||
"Added the 'z' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "b1f0bb9999d84d984ba7d9445e6846c36257b748",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3c606d3339e51b71968f7b00c08aea4177adb21e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-var-declaration-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Deleted the 'x' variable",
|
||||
"Deleted the 'y' variable",
|
||||
"Deleted the 'z' variable",
|
||||
"Deleted the 'x' variable",
|
||||
"Added the 'x' variable",
|
||||
"Added the 'y' variable",
|
||||
"Added the 'z' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "3c606d3339e51b71968f7b00c08aea4177adb21e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "318503c582b1ca270e3ad2ea23140699079c3d4c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-var-declaration-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Deleted the 'x' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "318503c582b1ca270e3ad2ea23140699079c3d4c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5df38338d708d301838ab06cf6df7c919a55d629"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-var-declaration-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Deleted the 'x' variable",
|
||||
"Deleted the 'y' variable",
|
||||
"Deleted the 'z' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "5df38338d708d301838ab06cf6df7c919a55d629",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e797ca2c748a6d42d67875240942d0876fd66cbc"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/variable.json
Normal file
122
test/corpus/diff-summaries/javascript/variable.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-variable-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Added the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "b0665d174f7073b730432253122aad996e5d8107",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "65b080b43d781c4d968431e2c1b5e003fa271ecc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Added the 'theVar2' identifier",
|
||||
"Added the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "65b080b43d781c4d968431e2c1b5e003fa271ecc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3e0e939113069492829e74bc313211d7a128eb03"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Replaced the 'theVar2' identifier with the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "3e0e939113069492829e74bc313211d7a128eb03",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bd17ce67d20168f3fd2f84b81d2b1477797e9697"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Replaced the 'theVar' identifier with the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "bd17ce67d20168f3fd2f84b81d2b1477797e9697",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "758e2f8e2e39c93a046cfe689be6db32cc598e31"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Deleted the 'theVar2' identifier",
|
||||
"Deleted the 'theVar' identifier",
|
||||
"Added the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "758e2f8e2e39c93a046cfe689be6db32cc598e31",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "57dc8212e58234b75d4bdb9b2c9f7a72ebd31a2b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Deleted the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "57dc8212e58234b75d4bdb9b2c9f7a72ebd31a2b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4f1602caaa3a8783fc4c0f0d25b55ae01b133f3d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Deleted the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "4f1602caaa3a8783fc4c0f0d25b55ae01b133f3d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "aab18e237ace91db31cea86a6c4c43aa094b446e"
|
||||
}]
|
122
test/corpus/diff-summaries/javascript/void-operator.json
Normal file
122
test/corpus/diff-summaries/javascript/void-operator.json
Normal file
@ -0,0 +1,122 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-void-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Added the 'void b()' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "985f2a1f80a8f14a094977b3cb7b7954ea471f72",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2b8dcd202799552a208693fa57781d5f94a221fc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-void-operator-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Added the 'void c()' operator",
|
||||
"Added the 'void b()' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "2b8dcd202799552a208693fa57781d5f94a221fc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "90df42884e61ce36d55bba822ff9d51192d3652b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-void-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Replaced the 'c' identifier with the 'b' identifier in the b() function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "90df42884e61ce36d55bba822ff9d51192d3652b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0e8578d337c1ea43f770ecc7b35a42a1127b98f6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-void-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Replaced the 'b' identifier with the 'c' identifier in the c() function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "0e8578d337c1ea43f770ecc7b35a42a1127b98f6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2ffa7539fbf6152c971daf44f5f41b66545dce3c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-void-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Deleted the 'void c()' operator",
|
||||
"Deleted the 'void b()' operator",
|
||||
"Added the 'void c()' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "2ffa7539fbf6152c971daf44f5f41b66545dce3c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "14d67983489a5cf7b5323cfaea5387a71e87f133"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-void-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Deleted the 'void b()' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "14d67983489a5cf7b5323cfaea5387a71e87f133",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a04a6116eb7a6f11c718e3d2aeafbae0039c933c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-void-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Deleted the 'void c()' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "a04a6116eb7a6f11c718e3d2aeafbae0039c933c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "921348c0db5c7371a9d154653925c2efbaf8826b"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/while-statement.json
Normal file
124
test/corpus/diff-summaries/javascript/while-statement.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-while-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Added the 'a' while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "19910077ac4d4997c8d93c429177a77105905c9a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e923a70e7ff5488bf4a5ecced60feefff1ba772f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-while-statement-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Added the 'b' while statement",
|
||||
"Added the 'a' while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "e923a70e7ff5488bf4a5ecced60feefff1ba772f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ae74e4e611b4ef018dd5faaf5075f99374d94140"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-while-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Replaced the 'b' identifier with the 'a' identifier",
|
||||
"Replaced the 'a' identifier with the 'b' identifier in the b() function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "ae74e4e611b4ef018dd5faaf5075f99374d94140",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cafba614530550cd3432a9c630392e0ccd6fda10"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-while-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Replaced the 'a' identifier with the 'b' identifier",
|
||||
"Replaced the 'b' identifier with the 'a' identifier in the a() function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "cafba614530550cd3432a9c630392e0ccd6fda10",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "30971b690b530993deb4f9c6746e3662f9212a87"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-while-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Deleted the 'b' while statement",
|
||||
"Deleted the 'a' while statement",
|
||||
"Added the 'b' while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "30971b690b530993deb4f9c6746e3662f9212a87",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "88089b9e62c2640b78de0eb699fff2be72d42bb4"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-while-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Deleted the 'a' while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "88089b9e62c2640b78de0eb699fff2be72d42bb4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "aa6096fcbd54d1ecc0050ef69fce4ce98543b167"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-while-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Deleted the 'b' while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "aa6096fcbd54d1ecc0050ef69fce4ce98543b167",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d5cb38d1a4261f5dc4f97f8d7d0762f26dbd70e3"
|
||||
}]
|
105
test/corpus/diff-summaries/template-string.json
Normal file
105
test/corpus/diff-summaries/template-string.json
Normal file
@ -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"
|
||||
}]
|
422
test/corpus/generated/javascript.json
Normal file
422
test/corpus/generated/javascript.json
Normal file
@ -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"
|
||||
}
|
||||
]
|
||||
}
|
||||
]
|
0
test/corpus/generators/.gitkeep
Normal file
0
test/corpus/generators/.gitkeep
Normal file
1
test/corpus/repos/javascript
Submodule
1
test/corpus/repos/javascript
Submodule
@ -0,0 +1 @@
|
||||
Subproject commit 4ec7dc112cd4ee7df857942392d9c0a9b1c73d25
|
Loading…
Reference in New Issue
Block a user