mirror of
https://github.com/github/semantic.git
synced 2024-12-23 23:11:50 +03:00
Try out moving project around
This commit is contained in:
parent
03c97ac5e7
commit
6cbfa91475
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 "tools/semantic-git-diff/test/corpus/repos/javascript"]
|
||||
path = tools/semantic-git-diff/test/corpus/repos/javascript
|
||||
url = https://github.com/rewinfrey/javascript.git
|
||||
|
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") "tools/semantic-git-diff/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.1.1
|
||||
synopsis: Initial project template from stack
|
||||
description: Please see README.md
|
||||
homepage: http://github.com/github/semantic-diff#readme
|
||||
@ -42,6 +42,7 @@ library
|
||||
, Renderer.Patch
|
||||
, Renderer.Split
|
||||
, Renderer.Summary
|
||||
, SemanticDiff
|
||||
, SES
|
||||
, Source
|
||||
, SourceSpan
|
||||
@ -83,25 +84,79 @@ library
|
||||
, protolude
|
||||
, wl-pprint-text
|
||||
, quickcheck-instances
|
||||
, gitlib
|
||||
, gitlib-libgit2
|
||||
, async-pool
|
||||
, optparse-applicative
|
||||
, regex-compat
|
||||
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-git-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
|
||||
, 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
|
||||
, semantic-diff
|
||||
, semantic-diff
|
||||
, text >= 1.2.1.3
|
||||
, these
|
||||
, vector
|
||||
, wl-pprint-text
|
||||
, process
|
||||
, optparse-applicative
|
||||
, MissingH
|
||||
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
|
||||
, monad-par
|
||||
, directory
|
||||
, 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
|
||||
@ -143,6 +198,32 @@ test-suite test
|
||||
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: aeson
|
||||
, async-pool
|
||||
, base
|
||||
, bytestring
|
||||
, filepath
|
||||
, gitlib
|
||||
, gitlib-libgit2
|
||||
, Glob
|
||||
, hspec >= 2.1.10
|
||||
, optparse-applicative
|
||||
, semantic-diff
|
||||
, split
|
||||
, tagged
|
||||
, text
|
||||
, containers
|
||||
, hspec-expectations-pretty-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
|
||||
|
154
src/SemanticDiff.hs
Normal file
154
src/SemanticDiff.hs
Normal file
@ -0,0 +1,154 @@
|
||||
{-# 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)
|
||||
|
||||
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-git-diff version " <> showVersion Library.version
|
||||
|
||||
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"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/anonymous-function.json
Normal file
124
test/corpus/diff-summaries/javascript/anonymous-function.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-anonymous-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Added an anonymous (a,b) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "e8b2b7fe36d673849485d794fb1cbd70190d690d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f236f9de5820f3ac23ff0e48b4f754fe5a320422"
|
||||
}
|
||||
,{
|
||||
"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": "f236f9de5820f3ac23ff0e48b4f754fe5a320422",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c5a550f71459ece7fff52e46bf861fd5532dfc54"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Added an anonymous (a,b) function",
|
||||
"Deleted an anonymous (b,c) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "c5a550f71459ece7fff52e46bf861fd5532dfc54",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8dfd0b811933dca1066fe42705a26bc5ba42f637"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Added an anonymous (b,c) function",
|
||||
"Deleted an anonymous (a,b) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "8dfd0b811933dca1066fe42705a26bc5ba42f637",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9bd1c3ac61ef7cb186edb551c3c91649fce7aca1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Deleted an anonymous (b,c) function",
|
||||
"Added an anonymous (b,c) function",
|
||||
"Deleted an anonymous (a,b) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "9bd1c3ac61ef7cb186edb551c3c91649fce7aca1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "84818bdaa0e92224ebead33361dd3bd8b511087f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Deleted an anonymous (a,b) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "84818bdaa0e92224ebead33361dd3bd8b511087f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7bb16bfa674880adab88defb193b412f79c6ce76"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-function.js": [
|
||||
"Deleted an anonymous (b,c) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-function.js"
|
||||
],
|
||||
"sha1": "7bb16bfa674880adab88defb193b412f79c6ce76",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ff4a6de884ce065c4e38bbed8c96ce7a09b777bb"
|
||||
}]
|
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Added an anonymous function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "ff4a6de884ce065c4e38bbed8c96ce7a09b777bb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a0134fd854f5580b38c603e8e66e60ff5499fa89"
|
||||
}
|
||||
,{
|
||||
"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": "a0134fd854f5580b38c603e8e66e60ff5499fa89",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3fcaedd3f7d11d4f51d77e9ed39a1ecf1e4fccc3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Added an anonymous function",
|
||||
"Deleted an anonymous function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "3fcaedd3f7d11d4f51d77e9ed39a1ecf1e4fccc3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "29c534eb67a3084722e0d75a88f4aba2fb04c244"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Added an anonymous function",
|
||||
"Deleted an anonymous function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "29c534eb67a3084722e0d75a88f4aba2fb04c244",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b55e2117636e608d14b5e02939e51462f01723b6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Deleted an anonymous function",
|
||||
"Added an anonymous function",
|
||||
"Deleted an anonymous function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "b55e2117636e608d14b5e02939e51462f01723b6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "67fa6d755e09b9aa4a56b4082d815a296429f143"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"anonymous-parameterless-function.js": [
|
||||
"Deleted an anonymous function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"anonymous-parameterless-function.js"
|
||||
],
|
||||
"sha1": "67fa6d755e09b9aa4a56b4082d815a296429f143",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "431436321eacb659cefa2faaed0bf3d1ef8dbec7"
|
||||
}
|
||||
,{
|
||||
"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": "431436321eacb659cefa2faaed0bf3d1ef8dbec7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "133af9a2d6a65f9f341f5450f0c0155ba7aaa5df"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/array.json
Normal file
124
test/corpus/diff-summaries/javascript/array.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-array-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Added the '[ \"item1\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "fa492d3a7bab9438e0b740da2a4dd00755e60ed0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "05d8de78bd5583e935bb654f0226dce1b83b8259"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Added the '[ \"item1\", \"item2\" ]' array",
|
||||
"Added the '[ \"item1\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "05d8de78bd5583e935bb654f0226dce1b83b8259",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a27344fe896967558a81ca648f65064cefcfd96e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Added the '[ \"item1\" ]' array",
|
||||
"Deleted the '[ \"item1\", \"item2\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "a27344fe896967558a81ca648f65064cefcfd96e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ec5039562b41e2b874996a4ceb3c11eb84996dec"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Added the '[ \"item1\", \"item2\" ]' array",
|
||||
"Deleted the '[ \"item1\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "ec5039562b41e2b874996a4ceb3c11eb84996dec",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a828418feb9848768acdd1281168900e7a2099d3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Deleted the '[ \"item1\", \"item2\" ]' array",
|
||||
"Added the '[ \"item1\", \"item2\" ]' array",
|
||||
"Deleted the '[ \"item1\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "a828418feb9848768acdd1281168900e7a2099d3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "97038c31b238efec98f41344cd0e7a7a4430c0a0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Deleted the '[ \"item1\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "97038c31b238efec98f41344cd0e7a7a4430c0a0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "97a0af9d53a6eec57cebc73ddc5f1187ed2278a7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-array-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"array.js": [
|
||||
"Deleted the '[ \"item1\", \"item2\" ]' array"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"array.js"
|
||||
],
|
||||
"sha1": "97a0af9d53a6eec57cebc73ddc5f1187ed2278a7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7fac5d7a13b841bd9a3ff68f5cdbe6f20d2182ca"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/arrow-function.json
Normal file
124
test/corpus/diff-summaries/javascript/arrow-function.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-arrow-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Added an anonymous (f, g) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "172bde4debafc2f284ac04afedb46f598f0907a4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "05933b89f2b33dc0dad71a9550a01acd71c539e8"
|
||||
}
|
||||
,{
|
||||
"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": "05933b89f2b33dc0dad71a9550a01acd71c539e8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "33214f2832d4307bb31ce2798d7998859db28ff1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-arrow-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Added an anonymous (f, g) function",
|
||||
"Deleted an anonymous (f, g) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "33214f2832d4307bb31ce2798d7998859db28ff1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d775da664a0ffcdf268de1ea01f6c2be863a2b62"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-arrow-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Added an anonymous (f, g) function",
|
||||
"Deleted an anonymous (f, g) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "d775da664a0ffcdf268de1ea01f6c2be863a2b62",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0d17cfb3854c792172c55c4be886ea82c38944e6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-arrow-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Deleted an anonymous (f, g) function",
|
||||
"Added an anonymous (f, g) function",
|
||||
"Deleted an anonymous (f, g) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "0d17cfb3854c792172c55c4be886ea82c38944e6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "289c6f83030658e80e803ddd9afc4a5d5de8d12c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-arrow-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Deleted an anonymous (f, g) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "289c6f83030658e80e803ddd9afc4a5d5de8d12c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8323d42a226595f5ad73216e4931072e0e62b244"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-arrow-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"arrow-function.js": [
|
||||
"Deleted an anonymous (f, g) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"arrow-function.js"
|
||||
],
|
||||
"sha1": "8323d42a226595f5ad73216e4931072e0e62b244",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2f2cf1310f873d0fd161b380b7eeded32ac59cb1"
|
||||
}]
|
123
test/corpus/diff-summaries/javascript/assignment.json
Normal file
123
test/corpus/diff-summaries/javascript/assignment.json
Normal file
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-assignment-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Added the 'x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "55e11835c0c544a3c27d14ebc62eef4b48f8cd3a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5f3ccff89676dff785e1f64e3454132d817bfc36"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Added the 'x' assignment",
|
||||
"Added the 'x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "5f3ccff89676dff785e1f64e3454132d817bfc36",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5369e879fd3e2c6600c6fb7535670bb723db82bd"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Added the 'x' assignment",
|
||||
"Deleted the 'x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "5369e879fd3e2c6600c6fb7535670bb723db82bd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "41e1fd6e19b5fad123bf3b84a658b24b8fc4126d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Added the 'x' assignment",
|
||||
"Deleted the 'x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "41e1fd6e19b5fad123bf3b84a658b24b8fc4126d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "60aa2f11f8907432a7269212a6afea5ea15a6f2c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Deleted the 'x' assignment",
|
||||
"Replaced '0' with '1' in an assignment to x"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "60aa2f11f8907432a7269212a6afea5ea15a6f2c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "723a7b08c780721393402d989dd53dd3e6e5672b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Deleted the 'x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "723a7b08c780721393402d989dd53dd3e6e5672b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "901819c66aa88da6b6b14b4250d54980cecd1234"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-assignment-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"assignment.js": [
|
||||
"Deleted the 'x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"assignment.js"
|
||||
],
|
||||
"sha1": "901819c66aa88da6b6b14b4250d54980cecd1234",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "38c11bda6a55b3c21ca0223aeef09c65d9e19b9e"
|
||||
}]
|
123
test/corpus/diff-summaries/javascript/bitwise-operator.json
Normal file
123
test/corpus/diff-summaries/javascript/bitwise-operator.json
Normal file
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-bitwise-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Added the 'i >> j' bitwise operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "cbe58e2de4353948478c7716d90fa22e6f430b3f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e00ee4c31366730302d1bd06e6359897dd94f02c"
|
||||
}
|
||||
,{
|
||||
"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": "e00ee4c31366730302d1bd06e6359897dd94f02c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6724780ecdbfccbc419d351fd0104959a90200b2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-bitwise-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Added the 'i >> j' bitwise operator",
|
||||
"Deleted the 'i >> k' bitwise operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "6724780ecdbfccbc419d351fd0104959a90200b2",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "83f1c96a797988568a6466a436d0ee8a1f95b054"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-bitwise-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Added the 'i >> k' bitwise operator",
|
||||
"Deleted the 'i >> j' bitwise operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "83f1c96a797988568a6466a436d0ee8a1f95b054",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c546b433a881c30583010d2ac6b4186a2c30c4bb"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-bitwise-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Deleted the 'i >> k' bitwise operator",
|
||||
"Replaced the 'j' identifier with the 'k' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "c546b433a881c30583010d2ac6b4186a2c30c4bb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "df100f5ba9f9c4901c42b1efce658b29e87ea029"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-bitwise-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Deleted the 'i >> j' bitwise operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "df100f5ba9f9c4901c42b1efce658b29e87ea029",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3e368d25cc3a3fb92993c5561becf428f03ff75b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-bitwise-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"bitwise-operator.js": [
|
||||
"Deleted the 'i >> k' bitwise operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"bitwise-operator.js"
|
||||
],
|
||||
"sha1": "3e368d25cc3a3fb92993c5561becf428f03ff75b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2b3a648ff2420e7e577c6ac2909dfdf09ec6d3bd"
|
||||
}]
|
86
test/corpus/diff-summaries/javascript/boolean-operator.json
Normal file
86
test/corpus/diff-summaries/javascript/boolean-operator.json
Normal file
@ -0,0 +1,86 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-boolean-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"boolean-operator.js": [
|
||||
"Added the 'i || j' boolean operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"boolean-operator.js"
|
||||
],
|
||||
"sha1": "431090fc86018346fe6fe6451088317d64412f5c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ccb11fa49f9987a72e26ef760eacc838ce4a43b7"
|
||||
}
|
||||
,{
|
||||
"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": "ccb11fa49f9987a72e26ef760eacc838ce4a43b7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ed62cd513db43b950517f730e69830ca467c841d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-boolean-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"boolean-operator.js": [
|
||||
"Deleted the 'i || j' boolean operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"boolean-operator.js"
|
||||
],
|
||||
"sha1": "f1250aa0e75b50c471588daf6428662e1c1adc46",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ee38b984d7c44aa2b198bef80d859d002bb546e3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-boolean-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"boolean-operator.js": [
|
||||
"Deleted the 'i && j' boolean operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"boolean-operator.js"
|
||||
],
|
||||
"sha1": "ee38b984d7c44aa2b198bef80d859d002bb546e3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3f6091d6fdebbc0f0d8134abe4135a004648fa08"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-boolean-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"boolean-operator.js": [
|
||||
"Deleted the 'i && j' boolean operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"boolean-operator.js"
|
||||
],
|
||||
"sha1": "3f6091d6fdebbc0f0d8134abe4135a004648fa08",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cbe58e2de4353948478c7716d90fa22e6f430b3f"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/chained-callbacks.json
Normal file
124
test/corpus/diff-summaries/javascript/chained-callbacks.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-chained-callbacks-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Added the 'this.map(…)' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "298fb331dea64b4fe4323fbb01c0b2578a425bcc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c5f3c51f8dd1fecfb3a62ded5fd477c701146b5e"
|
||||
}
|
||||
,{
|
||||
"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": "c5f3c51f8dd1fecfb3a62ded5fd477c701146b5e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "08ab7271bae8f27b35fdf8dcb7aec44b1132d5aa"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-callbacks-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Added the 'this.map(…)' method call",
|
||||
"Deleted the 'this.reduce(…)' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "08ab7271bae8f27b35fdf8dcb7aec44b1132d5aa",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "60bafa5a398c79d84d3dbf2b54777a67d1069c72"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-callbacks-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Added the 'this.reduce(…)' method call",
|
||||
"Deleted the 'this.map(…)' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "60bafa5a398c79d84d3dbf2b54777a67d1069c72",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b99ecde5f452b7f2e765d386fd89a3143cd2a7a3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-callbacks-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Deleted the 'this.reduce(…)' method call",
|
||||
"Added the 'this.reduce(…)' method call",
|
||||
"Deleted the 'this.map(…)' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "b99ecde5f452b7f2e765d386fd89a3143cd2a7a3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a2cc85026538bd98d696b1b9ee5aa6d3dcd4f572"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-callbacks-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Deleted the 'this.map(…)' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "a2cc85026538bd98d696b1b9ee5aa6d3dcd4f572",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cc4a75036f1e12213a1403fcfb29d8a329f09744"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-callbacks-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-callbacks.js": [
|
||||
"Deleted the 'this.reduce(…)' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-callbacks.js"
|
||||
],
|
||||
"sha1": "cc4a75036f1e12213a1403fcfb29d8a329f09744",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "95d141d5f4f92f171e7690e40239750e8d55e7da"
|
||||
}]
|
@ -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": "0d39978593de2568f3ab5b0db632c7091f305835",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "02e0c92e32e7486f7f3bfecb5ec7901a91b933c5"
|
||||
}
|
||||
,{
|
||||
"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": "02e0c92e32e7486f7f3bfecb5ec7901a91b933c5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4982cbccacaa37f8b98eb05b041be31bf5297b7c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-property-access.js": [
|
||||
"Added the 'returned.promise().done(…).fail(…)' return statement",
|
||||
"Deleted the 'returned.promise().done(…).fail(…)' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-property-access.js"
|
||||
],
|
||||
"sha1": "4982cbccacaa37f8b98eb05b041be31bf5297b7c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c8ab77841777008e7b161e300debf78e144756b0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-property-access.js": [
|
||||
"Added the 'returned.promise().done(…).fail(…)' return statement",
|
||||
"Deleted the 'returned.promise().done(…).fail(…)' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-property-access.js"
|
||||
],
|
||||
"sha1": "c8ab77841777008e7b161e300debf78e144756b0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7fb67a5e9a60e16d39e521fd3bad8727ed8db378"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-chained-property-access-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"chained-property-access.js": [
|
||||
"Deleted the 'returned.promise().done(…).fail(…)' return statement",
|
||||
"Added the 'returned.promise().done(…).fail(…)' return statement",
|
||||
"Deleted the 'returned.promise().done(…).fail(…)' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"chained-property-access.js"
|
||||
],
|
||||
"sha1": "7fb67a5e9a60e16d39e521fd3bad8727ed8db378",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ca4793d8cae63c39d45775e17541fe7a156c945b"
|
||||
}
|
||||
,{
|
||||
"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": "ca4793d8cae63c39d45775e17541fe7a156c945b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "58f1fb0cc9f077dec7737a31e5bd120d70623a8d"
|
||||
}
|
||||
,{
|
||||
"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": "58f1fb0cc9f077dec7737a31e5bd120d70623a8d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "298fb331dea64b4fe4323fbb01c0b2578a425bcc"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/class.json
Normal file
124
test/corpus/diff-summaries/javascript/class.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-class-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Added the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "cf779d502bc851d68864656c5160ca1ff103ca7b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "915375b26040eb52340a39e93c4530ba0fa1744c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Added the 'Foo' class",
|
||||
"Added the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "915375b26040eb52340a39e93c4530ba0fa1744c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2a3ea9a5a99b738cfb766ff64b75748a829f8c52"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Added the 'Foo' class",
|
||||
"Deleted the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "2a3ea9a5a99b738cfb766ff64b75748a829f8c52",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e24adf2f9da4a1445c4cf6dc11490ca36887aad9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Added the 'Foo' class",
|
||||
"Deleted the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "e24adf2f9da4a1445c4cf6dc11490ca36887aad9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c066ead4c8412141afed3629577b7e24da2485da"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Deleted the 'Foo' class",
|
||||
"Added the 'Foo' class",
|
||||
"Deleted the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "c066ead4c8412141afed3629577b7e24da2485da",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9f9eac53aa70887ab98669de440007036c932643"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Deleted the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "9f9eac53aa70887ab98669de440007036c932643",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "dae1e9b59446a1aaeb81cf4ed156f160b01098d6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-class-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"class.js": [
|
||||
"Deleted the 'Foo' class"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"class.js"
|
||||
],
|
||||
"sha1": "dae1e9b59446a1aaeb81cf4ed156f160b01098d6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "fa492d3a7bab9438e0b740da2a4dd00755e60ed0"
|
||||
}]
|
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": "8e9465a057e544de7926bfee045371e151262b37",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "affe6a428f9a8aa0963bb07c4028e3466dba26ec"
|
||||
}
|
||||
,{
|
||||
"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": "affe6a428f9a8aa0963bb07c4028e3466dba26ec",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7a0425207d1b61f8fff05006d40964eabc44040c"
|
||||
}
|
||||
,{
|
||||
"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": "7a0425207d1b61f8fff05006d40964eabc44040c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4a3f9ce608a12e1c6106fd46350ad19e5835d31f"
|
||||
}
|
||||
,{
|
||||
"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": "4a3f9ce608a12e1c6106fd46350ad19e5835d31f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a62b66d9d1db7c14d8427d44622f7213cd31eef1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comma-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comma-operator.js": [
|
||||
"Deleted the 'c' assignment",
|
||||
"Added the 'c' assignment",
|
||||
"Deleted the 'a' assignment",
|
||||
"Deleted the 'b' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comma-operator.js"
|
||||
],
|
||||
"sha1": "a62b66d9d1db7c14d8427d44622f7213cd31eef1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e53f041d3a357dea5f8b536b78f6c989096342c6"
|
||||
}
|
||||
,{
|
||||
"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": "e53f041d3a357dea5f8b536b78f6c989096342c6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "78e0935f30388de986c5c1b16f48acccd6f4a26f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comma-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comma-operator.js": [
|
||||
"Deleted the 'c' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comma-operator.js"
|
||||
],
|
||||
"sha1": "78e0935f30388de986c5c1b16f48acccd6f4a26f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b4a653f9eafddd6ddabce75bab6f1de384618add"
|
||||
}]
|
123
test/corpus/diff-summaries/javascript/comment.json
Normal file
123
test/corpus/diff-summaries/javascript/comment.json
Normal file
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-comment-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Added the '// This is a property' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "c367cef2a2ab4f6c19c197ff79c0e633b62e30b4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cddae3787c876d2d1422b1e8a20b70fff43ea791"
|
||||
}
|
||||
,{
|
||||
"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": "cddae3787c876d2d1422b1e8a20b70fff43ea791",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a92356ef5dd2872d9deca3ca0ccbc96acde7e7c9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comment-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Deleted the '/*\n * This is a method\n*/' comment",
|
||||
"Added the '// This is a property' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "a92356ef5dd2872d9deca3ca0ccbc96acde7e7c9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1b6142218dba998b1d8e30ff04ab3956af156d89"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comment-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Added the '/*\n * This is a method\n*/' comment",
|
||||
"Deleted the '// This is a property' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "1b6142218dba998b1d8e30ff04ab3956af156d89",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8e72d96f78fe6aa854538e0ad4b905f847220637"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comment-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Deleted the '/*\n * This is a method\n*/' comment",
|
||||
"Replaced the '// This is a property' comment with the '/*\n * This is a method\n*/' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "8e72d96f78fe6aa854538e0ad4b905f847220637",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "26d973746782342270438610ac35e6f88147e85a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comment-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Deleted the '// This is a property' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "26d973746782342270438610ac35e6f88147e85a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0559ba4c7ac24ec74a05da45e9fc7c8d69af3604"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-comment-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"comment.js": [
|
||||
"Deleted the '/*\n * This is a method\n*/' comment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"comment.js"
|
||||
],
|
||||
"sha1": "0559ba4c7ac24ec74a05da45e9fc7c8d69af3604",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5b6687475c3b7f8c43a128b52e6c4e9220558a04"
|
||||
}]
|
123
test/corpus/diff-summaries/javascript/constructor-call.json
Normal file
123
test/corpus/diff-summaries/javascript/constructor-call.json
Normal file
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-constructor-call-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Added the 'module.Klass(1, \"two\")' constructor"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "56ac0498e3eca9490af686d48b36ddaaaf867dcc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ad41d965f174f829905e7c3e1af85e4ac66515c0"
|
||||
}
|
||||
,{
|
||||
"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": "ad41d965f174f829905e7c3e1af85e4ac66515c0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a373f053576064a918b1046e076f84522cf5bd91"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-constructor-call-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Added the 'module.Klass(1, \"two\")' constructor",
|
||||
"Deleted the 'module.Klass(1, \"three\")' constructor"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "a373f053576064a918b1046e076f84522cf5bd91",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f79590f526ca63035f84fa6c5863f913c54cf138"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-constructor-call-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Added the 'module.Klass(1, \"three\")' constructor",
|
||||
"Deleted the 'module.Klass(1, \"two\")' constructor"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "f79590f526ca63035f84fa6c5863f913c54cf138",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1f6e48e9190f5c819cec62e4d8a4f649696d9c78"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-constructor-call-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Deleted the 'module.Klass(1, \"three\")' constructor",
|
||||
"Replaced the \"two\" string with the \"three\" string in the module.Klass(1, \"three\") method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "1f6e48e9190f5c819cec62e4d8a4f649696d9c78",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6b576267384568958b95ec13e2bd6a03e91b2566"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-constructor-call-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"constructor-call.js": [
|
||||
"Deleted the 'module.Klass(1, \"two\")' constructor"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"constructor-call.js"
|
||||
],
|
||||
"sha1": "6b576267384568958b95ec13e2bd6a03e91b2566",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c7c67fb74a7c2bc37086788149ddbdb977698179"
|
||||
}
|
||||
,{
|
||||
"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": "c7c67fb74a7c2bc37086788149ddbdb977698179",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7f626789377b5fd3eea7b354c6e5a1cc5fc2e265"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/delete-operator.json
Normal file
124
test/corpus/diff-summaries/javascript/delete-operator.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-delete-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Added the 'delete thing['prop']' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "bc15aec1c4c4587cd5b4d204e3f00feec92121dc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f22024cd7638d58322baf56ac7f4f92d4362ef72"
|
||||
}
|
||||
,{
|
||||
"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": "f22024cd7638d58322baf56ac7f4f92d4362ef72",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9826ff64f0489fd1a68ff364565921c9963ebb1b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-delete-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Added the 'delete thing['prop']' operator",
|
||||
"Deleted the 'delete thing.prop' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "9826ff64f0489fd1a68ff364565921c9963ebb1b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "205aa4c322bbea472e7b9f2c304b095a228cd19f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-delete-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Added the 'delete thing.prop' operator",
|
||||
"Deleted the 'delete thing['prop']' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "205aa4c322bbea472e7b9f2c304b095a228cd19f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "97b0347b390b2458f820f0b149068f9461a435cf"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-delete-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Deleted the 'delete thing.prop' operator",
|
||||
"Added the 'delete thing.prop' operator",
|
||||
"Deleted the 'delete thing['prop']' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "97b0347b390b2458f820f0b149068f9461a435cf",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6fa3a94c630696908821c630c84c2a88178435e0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-delete-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Deleted the 'delete thing['prop']' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "6fa3a94c630696908821c630c84c2a88178435e0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0ef9281385ae4b7a3f66369a69804ad14f2da122"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-delete-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"delete-operator.js": [
|
||||
"Deleted the 'delete thing.prop' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"delete-operator.js"
|
||||
],
|
||||
"sha1": "0ef9281385ae4b7a3f66369a69804ad14f2da122",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0e5929ffe5c88dd824b05f48b9025ccfa67f9c04"
|
||||
}]
|
126
test/corpus/diff-summaries/javascript/do-while-statement.json
Normal file
126
test/corpus/diff-summaries/javascript/do-while-statement.json
Normal file
@ -0,0 +1,126 @@
|
||||
[{
|
||||
"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": "150d2c57e7375a0937ec2d1f84faed6f49b55c84",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "80e5befa1751f87dafa16541496043833f5a239f"
|
||||
}
|
||||
,{
|
||||
"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": "80e5befa1751f87dafa16541496043833f5a239f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8cf5d1e10a9fe9e8cef1f470748f27ab8d52524a"
|
||||
}
|
||||
,{
|
||||
"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": "8cf5d1e10a9fe9e8cef1f470748f27ab8d52524a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6e59d498dc96fe53cab37f7a1e21e5c0cbe10bd5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-do-while-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"do-while-statement.js": [
|
||||
"Added the 'false' do/while statement",
|
||||
"Added the 'true' do/while statement",
|
||||
"Deleted the 'true' do/while statement",
|
||||
"Deleted the 'true' do/while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"do-while-statement.js"
|
||||
],
|
||||
"sha1": "6e59d498dc96fe53cab37f7a1e21e5c0cbe10bd5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "dbedc5a5e0bcad94bbc6badbb56a16fc6111d7c8"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-do-while-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"do-while-statement.js": [
|
||||
"Added the 'true' do/while statement",
|
||||
"Deleted the 'true' do/while statement",
|
||||
"Deleted the 'true' do/while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"do-while-statement.js"
|
||||
],
|
||||
"sha1": "dbedc5a5e0bcad94bbc6badbb56a16fc6111d7c8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d94157bbf358bf818538eab367b7183aab63aead"
|
||||
}
|
||||
,{
|
||||
"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": "d94157bbf358bf818538eab367b7183aab63aead",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c1abae4a248c57a5d995690e5d93ac37dcb64843"
|
||||
}
|
||||
,{
|
||||
"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": "c1abae4a248c57a5d995690e5d93ac37dcb64843",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "66eecf807ba1e2964d6937be2095ef24a1676269"
|
||||
}]
|
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": "cbcf093735696437716562b80be6c19a66e585c0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ca6a2046f7136a862b35ca45ab30af4dae337197"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Added the 'false' return statement",
|
||||
"Added 'false'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "ca6a2046f7136a862b35ca45ab30af4dae337197",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b6603c3a83c1dd23aeb232bd8de52e31980845fe"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Deleted the 'false' return statement",
|
||||
"Added 'false'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "b6603c3a83c1dd23aeb232bd8de52e31980845fe",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a5f742707a6a188bfc426643e678f89f22396ce1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Added the 'false' return statement",
|
||||
"Deleted 'false'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "a5f742707a6a188bfc426643e678f89f22396ce1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0582e7c825b7eb6cdc0e0d3417f723e08ffe62d6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Deleted the 'false' return statement",
|
||||
"Added the 'false' return statement",
|
||||
"Deleted 'false'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "0582e7c825b7eb6cdc0e0d3417f723e08ffe62d6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f498d3d2a0d563503827bc3e524bafddfec2eebf"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Deleted 'false'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "f498d3d2a0d563503827bc3e524bafddfec2eebf",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3d9f91f9c665ce798bed86f5ba2831d4e084edb4"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-false-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"false.js": [
|
||||
"Deleted the 'false' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"false.js"
|
||||
],
|
||||
"sha1": "3d9f91f9c665ce798bed86f5ba2831d4e084edb4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cf779d502bc851d68864656c5160ca1ff103ca7b"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/for-in-statement.json
Normal file
124
test/corpus/diff-summaries/javascript/for-in-statement.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"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": "a49b3cc79bf0a423e6474f02d4f9b2deae2cf7aa",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0a7c6659f5ec71c2b1fa3e6e2bb4496a93f32f61"
|
||||
}
|
||||
,{
|
||||
"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": "0a7c6659f5ec71c2b1fa3e6e2bb4496a93f32f61",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "99cf353eb02deb90fb186c3f329a08b0d4d8d6af"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-in-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-in-statement.js": [
|
||||
"Deleted the 'item in items' for statement",
|
||||
"Added the 'thing in things' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-in-statement.js"
|
||||
],
|
||||
"sha1": "99cf353eb02deb90fb186c3f329a08b0d4d8d6af",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f581d7c8f2909f9bbfd0bd22aa842d4f75024922"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-in-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-in-statement.js": [
|
||||
"Added the 'item in items' for statement",
|
||||
"Deleted the 'thing in things' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-in-statement.js"
|
||||
],
|
||||
"sha1": "f581d7c8f2909f9bbfd0bd22aa842d4f75024922",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3d00da198e8cb46729d6731b25996989a2bbc861"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-in-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-in-statement.js": [
|
||||
"Deleted the 'item in items' for statement",
|
||||
"Added the 'item in items' for statement",
|
||||
"Deleted the 'thing in things' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-in-statement.js"
|
||||
],
|
||||
"sha1": "3d00da198e8cb46729d6731b25996989a2bbc861",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c89f407311b549fca61cbaf71bb56d3ee6dc7454"
|
||||
}
|
||||
,{
|
||||
"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": "c89f407311b549fca61cbaf71bb56d3ee6dc7454",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "36ffd9416fc0678a6934d4b8669d19e7b9a6750b"
|
||||
}
|
||||
,{
|
||||
"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": "36ffd9416fc0678a6934d4b8669d19e7b9a6750b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "12621d999238618e3a862f232779862ba803a778"
|
||||
}]
|
@ -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": "17f5abea194c00c30becb942c3027e39e06587e5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a21b599a32324604d9112ede61a3088b6cb4b29f"
|
||||
}
|
||||
,{
|
||||
"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": "a21b599a32324604d9112ede61a3088b6cb4b29f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "36f946485face8ac155e070ddc07f61f5f7bebde"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-loop-with-in-statement.js": [
|
||||
"Deleted 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": "36f946485face8ac155e070ddc07f61f5f7bebde",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "42d0c83d21fbbfb73a8e125d6c89a5a982fc2ded"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-loop-with-in-statement.js": [
|
||||
"Added the 'otherKey in something && i = 0; i < n; i++' for statement",
|
||||
"Deleted the 'key in something && i = 0; i < n; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-loop-with-in-statement.js"
|
||||
],
|
||||
"sha1": "42d0c83d21fbbfb73a8e125d6c89a5a982fc2ded",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "61fdb98bf516ab55f4b85780c01bd2e12b67ddcb"
|
||||
}
|
||||
,{
|
||||
"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",
|
||||
"Added the 'otherKey in something && i = 0; i < n; i++' for statement",
|
||||
"Deleted the 'key in something && i = 0; i < n; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-loop-with-in-statement.js"
|
||||
],
|
||||
"sha1": "61fdb98bf516ab55f4b85780c01bd2e12b67ddcb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a3240e7ca5052ea60f693dce79bfddf93df68996"
|
||||
}
|
||||
,{
|
||||
"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": "a3240e7ca5052ea60f693dce79bfddf93df68996",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2815282baf54846662365cb1ab25ff93a6616022"
|
||||
}
|
||||
,{
|
||||
"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": "2815282baf54846662365cb1ab25ff93a6616022",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6d12c26a06d1329fb2747fa5450d0d1daa5315b4"
|
||||
}]
|
125
test/corpus/diff-summaries/javascript/for-of-statement.json
Normal file
125
test/corpus/diff-summaries/javascript/for-of-statement.json
Normal file
@ -0,0 +1,125 @@
|
||||
[{
|
||||
"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": "6d12c26a06d1329fb2747fa5450d0d1daa5315b4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "95e422908cefb7b204b7f8338bb74f09a7d40826"
|
||||
}
|
||||
,{
|
||||
"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": "95e422908cefb7b204b7f8338bb74f09a7d40826",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f33d7cbfde20a878483d6c3cc407018850490900"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-of-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-of-statement.js": [
|
||||
"Deleted the 'thing of things' for statement",
|
||||
"Added the 'item of items' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-of-statement.js"
|
||||
],
|
||||
"sha1": "f33d7cbfde20a878483d6c3cc407018850490900",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a53ae88670f65b2672416d50596c0871ad7ba7cd"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-of-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-of-statement.js": [
|
||||
"Added the 'thing of things' for statement",
|
||||
"Deleted the 'item of items' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-of-statement.js"
|
||||
],
|
||||
"sha1": "a53ae88670f65b2672416d50596c0871ad7ba7cd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7a4860e91d4f6af74ee726b63bf54c331a26601f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-of-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-of-statement.js": [
|
||||
"Deleted the 'thing of things' for statement",
|
||||
"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": "7a4860e91d4f6af74ee726b63bf54c331a26601f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "73838673579b3978b898a7ca10ff1695ca578d1b"
|
||||
}
|
||||
,{
|
||||
"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": "73838673579b3978b898a7ca10ff1695ca578d1b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "31b06acc145c0e425fc6d20dc235f3d852e4693e"
|
||||
}
|
||||
,{
|
||||
"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": "31b06acc145c0e425fc6d20dc235f3d852e4693e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b8093b25382e8511330d32163f647d8091652050"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/for-statement.json
Normal file
124
test/corpus/diff-summaries/javascript/for-statement.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"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": "fed990263904999ef2b80934ed1a3881d7cf7056",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "58a0286b88f63b9bbb3896bab90a71feea971f25"
|
||||
}
|
||||
,{
|
||||
"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": "58a0286b88f63b9bbb3896bab90a71feea971f25",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8f86190a63a1872eb2d45b9317fbdf6d105bd211"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-statement.js": [
|
||||
"Deleted 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": "8f86190a63a1872eb2d45b9317fbdf6d105bd211",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "71c94fa354c1a5f847c2c21d0a1151f7337625a9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-statement.js": [
|
||||
"Added the 'i = 0, init(); i < 100; i++' for statement",
|
||||
"Deleted the 'i = 0, init(); i < 10; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-statement.js"
|
||||
],
|
||||
"sha1": "71c94fa354c1a5f847c2c21d0a1151f7337625a9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e6851d26c6040978b859a83b6c6bb721fddf6957"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-for-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"for-statement.js": [
|
||||
"Deleted the 'i = 0, init(); i < 100; i++' for statement",
|
||||
"Added the 'i = 0, init(); i < 100; i++' for statement",
|
||||
"Deleted the 'i = 0, init(); i < 10; i++' for statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"for-statement.js"
|
||||
],
|
||||
"sha1": "e6851d26c6040978b859a83b6c6bb721fddf6957",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3a39a9788a1263dbfb596a58b1c6b8e60a7f4614"
|
||||
}
|
||||
,{
|
||||
"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": "3a39a9788a1263dbfb596a58b1c6b8e60a7f4614",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "05b927a87e3699d82e4e054f2b543db402ee2c41"
|
||||
}
|
||||
,{
|
||||
"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": "05b927a87e3699d82e4e054f2b543db402ee2c41",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "55e11835c0c544a3c27d14ebc62eef4b48f8cd3a"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/function-call-args.json
Normal file
124
test/corpus/diff-summaries/javascript/function-call-args.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"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": "2311700298627f011623e053dcffce4d08fb2fa5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3a034bfaf70eae77f3dc1e43d934f78c41104c7d"
|
||||
}
|
||||
,{
|
||||
"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": "3a034bfaf70eae77f3dc1e43d934f78c41104c7d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d13bfcd449c3459e307247a4db7d139260efec5c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-args-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call-args.js": [
|
||||
"Added the 'someFunction(1, \"string\", …, true)' function call",
|
||||
"Deleted the 'someFunction(1, \"otherString\", …, false)' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call-args.js"
|
||||
],
|
||||
"sha1": "d13bfcd449c3459e307247a4db7d139260efec5c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "40bb22fddcf563e0466e11a6f7e8487f3542ac73"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-args-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call-args.js": [
|
||||
"Added the 'someFunction(1, \"otherString\", …, false)' function call",
|
||||
"Deleted the 'someFunction(1, \"string\", …, true)' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call-args.js"
|
||||
],
|
||||
"sha1": "40bb22fddcf563e0466e11a6f7e8487f3542ac73",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "eeb76aed7b218d3838921ffb5ddf387c49d26a42"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-args-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call-args.js": [
|
||||
"Deleted the 'someFunction(1, \"otherString\", …, false)' function call",
|
||||
"Added the 'someFunction(1, \"otherString\", …, false)' function call",
|
||||
"Deleted the 'someFunction(1, \"string\", …, true)' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call-args.js"
|
||||
],
|
||||
"sha1": "eeb76aed7b218d3838921ffb5ddf387c49d26a42",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f1809a2391fb4d96c2abc1285453ce4adfd85f38"
|
||||
}
|
||||
,{
|
||||
"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": "f1809a2391fb4d96c2abc1285453ce4adfd85f38",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "44f10969631864287c36cf61e20200c1a0b04033"
|
||||
}
|
||||
,{
|
||||
"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": "44f10969631864287c36cf61e20200c1a0b04033",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "56ac0498e3eca9490af686d48b36ddaaaf867dcc"
|
||||
}]
|
123
test/corpus/diff-summaries/javascript/function-call.json
Normal file
123
test/corpus/diff-summaries/javascript/function-call.json
Normal file
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-function-call-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Added the 'someFunction(arg1, \"arg2\")' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "95d141d5f4f92f171e7690e40239750e8d55e7da",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3ea897b4631c2bf04b22d44ef9e566eae28ff43a"
|
||||
}
|
||||
,{
|
||||
"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": "3ea897b4631c2bf04b22d44ef9e566eae28ff43a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2dabb52c0b3fc57ab94cd911d0290d14b554a2f1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Added the 'someFunction(arg1, \"arg2\")' function call",
|
||||
"Deleted the 'someFunction(arg1, \"arg3\")' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "2dabb52c0b3fc57ab94cd911d0290d14b554a2f1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "263fedbfb30e5506e4b040ad61f87e8394d0f22d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Added the 'someFunction(arg1, \"arg3\")' function call",
|
||||
"Deleted the 'someFunction(arg1, \"arg2\")' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "263fedbfb30e5506e4b040ad61f87e8394d0f22d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "afafcf401c1ee7f87298287d8e415fdd0e7a9b97"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Deleted the 'someFunction(arg1, \"arg3\")' function call",
|
||||
"Replaced the \"arg2\" string with the \"arg3\" string in the someFunction(arg1, \"arg3\") function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "afafcf401c1ee7f87298287d8e415fdd0e7a9b97",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c447ceeba03db7d08a4557f644ef2fca1a96effc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-call-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function-call.js": [
|
||||
"Deleted the 'someFunction(arg1, \"arg2\")' function call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function-call.js"
|
||||
],
|
||||
"sha1": "c447ceeba03db7d08a4557f644ef2fca1a96effc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "02e6e6396e2587bfd43970031a36252f2a3f22b2"
|
||||
}
|
||||
,{
|
||||
"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": "02e6e6396e2587bfd43970031a36252f2a3f22b2",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "82f873975d82ce87bb75e9b0aacf08b3b34834cd"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/function.json
Normal file
124
test/corpus/diff-summaries/javascript/function.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Added an anonymous (arg1, arg2) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "7fac5d7a13b841bd9a3ff68f5cdbe6f20d2182ca",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "78038815a1ecc43f3634b78f364898ae0bc0fc70"
|
||||
}
|
||||
,{
|
||||
"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": "78038815a1ecc43f3634b78f364898ae0bc0fc70",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f9f88a393f11300c59a97615ab113aeec32977a6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Added an anonymous (arg1, arg2) function",
|
||||
"Deleted an anonymous (arg1, arg2) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "f9f88a393f11300c59a97615ab113aeec32977a6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "85ee90f769eb43b4d91594d4b736b28731bdf343"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Added an anonymous (arg1, arg2) function",
|
||||
"Deleted an anonymous (arg1, arg2) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "85ee90f769eb43b4d91594d4b736b28731bdf343",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ad24dbe91caaf0eed918099fb60eb5d4ce9b447f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Deleted an anonymous (arg1, arg2) function",
|
||||
"Added an anonymous (arg1, arg2) function",
|
||||
"Deleted an anonymous (arg1, arg2) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "ad24dbe91caaf0eed918099fb60eb5d4ce9b447f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "066bdaa70bd447c702f2c25ecfe6cb1ded40dd5f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Deleted an anonymous (arg1, arg2) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "066bdaa70bd447c702f2c25ecfe6cb1ded40dd5f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "837b627d35ac2a2152d5a1908055c912fff17f2e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"function.js": [
|
||||
"Deleted an anonymous (arg1, arg2) function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"function.js"
|
||||
],
|
||||
"sha1": "837b627d35ac2a2152d5a1908055c912fff17f2e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "172bde4debafc2f284ac04afedb46f598f0907a4"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/generator-function.json
Normal file
124
test/corpus/diff-summaries/javascript/generator-function.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-generator-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Added the 'generateStuff' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "2f2cf1310f873d0fd161b380b7eeded32ac59cb1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0fa30a49bdc004ac54536ba644bb9c3aac277657"
|
||||
}
|
||||
,{
|
||||
"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": "0fa30a49bdc004ac54536ba644bb9c3aac277657",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "66da496c2e4cd5cd2dfcd9e0e008d5935aa9447d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-generator-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Added the 'generateStuff' function",
|
||||
"Deleted the 'generateNewStuff' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "66da496c2e4cd5cd2dfcd9e0e008d5935aa9447d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c3749812404d2b8ce48d858e6930a39c6205bb01"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-generator-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Added the 'generateNewStuff' function",
|
||||
"Deleted the 'generateStuff' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "c3749812404d2b8ce48d858e6930a39c6205bb01",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "83f6cb79c4eb628b4c7233d417fa7cfa5fe368ec"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-generator-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Deleted the 'generateNewStuff' function",
|
||||
"Added the 'generateNewStuff' function",
|
||||
"Deleted the 'generateStuff' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "83f6cb79c4eb628b4c7233d417fa7cfa5fe368ec",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9a2afda62b7bc547a118a77bc674115008af0a68"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-generator-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Deleted the 'generateStuff' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "9a2afda62b7bc547a118a77bc674115008af0a68",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5ed821780dd73b7b59ebd6f572a98362bafb10a1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-generator-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"generator-function.js": [
|
||||
"Deleted the 'generateNewStuff' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"generator-function.js"
|
||||
],
|
||||
"sha1": "5ed821780dd73b7b59ebd6f572a98362bafb10a1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1bb9688393fd59b59ff2f59c16fae5e032ede0ac"
|
||||
}]
|
123
test/corpus/diff-summaries/javascript/identifier.json
Normal file
123
test/corpus/diff-summaries/javascript/identifier.json
Normal file
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-identifier-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Added the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "f956fe4ea44f5d38071a3c8a5a5342259ff9bb28",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7a8561f6a6dc0c1933517957bc717928e70549e8"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Added the 'theVar2' identifier",
|
||||
"Added the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "7a8561f6a6dc0c1933517957bc717928e70549e8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "37d6e043b9a03b37499115414498d411e33e195f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Added the 'theVar' identifier",
|
||||
"Deleted the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "37d6e043b9a03b37499115414498d411e33e195f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f23bc64c441f0252c79fe653f2350a1564e96b3a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Added the 'theVar2' identifier",
|
||||
"Deleted the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "f23bc64c441f0252c79fe653f2350a1564e96b3a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9d1235e2bd0d5bc32c1cf31ecb3e6ac711724551"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Deleted the 'theVar2' identifier",
|
||||
"Replaced the 'theVar' identifier with the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "9d1235e2bd0d5bc32c1cf31ecb3e6ac711724551",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "78be36d91654fb90d935fd09bc3d0fc0e9a712ba"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Deleted the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "78be36d91654fb90d935fd09bc3d0fc0e9a712ba",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e686b19de26cd69e1c16aceaf22aebdcabf2f427"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-identifier-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"identifier.js": [
|
||||
"Deleted the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"identifier.js"
|
||||
],
|
||||
"sha1": "e686b19de26cd69e1c16aceaf22aebdcabf2f427",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d50748ed7b3cffe454cf051e79a391b70cb1f55d"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/if-else.json
Normal file
124
test/corpus/diff-summaries/javascript/if-else.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-if-else-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Added the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "a2cd4ace03910aa5670e4c57a0054e6ff3f7d2f4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c4853824d5fa169d19a1620216b784cbf54b9478"
|
||||
}
|
||||
,{
|
||||
"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": "c4853824d5fa169d19a1620216b784cbf54b9478",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "76f2238bcc76cc1a0b44d71d606b8a4e28b8b8a7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-else-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Deleted the 'a' if statement",
|
||||
"Added the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "76f2238bcc76cc1a0b44d71d606b8a4e28b8b8a7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3d29588c4c9aa76231367e4fbbc9aeebc43bfac6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-else-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Added the 'a' if statement",
|
||||
"Deleted the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "3d29588c4c9aa76231367e4fbbc9aeebc43bfac6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "99575933ce84e80ec39132f3f2a67c20ae9a1f67"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-else-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Deleted the 'a' if statement",
|
||||
"Added the 'a' if statement",
|
||||
"Deleted the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "99575933ce84e80ec39132f3f2a67c20ae9a1f67",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9e92f4abe96e1ef862af2d39a5844f30c54bdcad"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-else-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Deleted the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "9e92f4abe96e1ef862af2d39a5844f30c54bdcad",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5cd59129fb8027de184f9e3f7d741570694542fe"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-else-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if-else.js": [
|
||||
"Deleted the 'a' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if-else.js"
|
||||
],
|
||||
"sha1": "5cd59129fb8027de184f9e3f7d741570694542fe",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "82ac9049dc6dcbfef96c1c8c65501872466b44fb"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/if.json
Normal file
124
test/corpus/diff-summaries/javascript/if.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-if-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Added the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "fcbc798fe671ee47690ed91b7645bbd2be9cd7eb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6086acfb25b3daae1fba0b61f25ede157c6f1bf6"
|
||||
}
|
||||
,{
|
||||
"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": "6086acfb25b3daae1fba0b61f25ede157c6f1bf6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "076df420ab7cb21d91e455cb209fcbcb237caa60"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Deleted the 'a.b' if statement",
|
||||
"Added the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "076df420ab7cb21d91e455cb209fcbcb237caa60",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "90dd9b172fe4001ce749aa41845a99f46156db5d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Added the 'a.b' if statement",
|
||||
"Deleted the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "90dd9b172fe4001ce749aa41845a99f46156db5d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b52f46756e4c5532c530ce6c9da0e87ef6d58584"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Deleted the 'a.b' if statement",
|
||||
"Added the 'a.b' if statement",
|
||||
"Deleted the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "b52f46756e4c5532c530ce6c9da0e87ef6d58584",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0bcd5d197d77e38caa2c3f031a8ced754750e07b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Deleted the 'x' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "0bcd5d197d77e38caa2c3f031a8ced754750e07b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ef728263696e025986880d1343da6410a5b3dd0b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-if-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"if.js": [
|
||||
"Deleted the 'a.b' if statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"if.js"
|
||||
],
|
||||
"sha1": "ef728263696e025986880d1343da6410a5b3dd0b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a2cd4ace03910aa5670e4c57a0054e6ff3f7d2f4"
|
||||
}]
|
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"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": "5c0c3689340b3b739532d2312d2eb95be94926ce",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cd70e5a520ed9ffc7d41937197740c33a39a808e"
|
||||
}
|
||||
,{
|
||||
"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": "cd70e5a520ed9ffc7d41937197740c33a39a808e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6d4f17e5ab3ba5871604c035ee8d2522266d30d2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-assignment-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-assignment-operator.js": [
|
||||
"Added the 'x' math assignment",
|
||||
"Deleted the 'x' math assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-assignment-operator.js"
|
||||
],
|
||||
"sha1": "6d4f17e5ab3ba5871604c035ee8d2522266d30d2",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "38007acda717c61cb2a9f9656832345b7b1c0be5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-assignment-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-assignment-operator.js": [
|
||||
"Added the 'x' math assignment",
|
||||
"Deleted the 'x' math assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-assignment-operator.js"
|
||||
],
|
||||
"sha1": "38007acda717c61cb2a9f9656832345b7b1c0be5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "641d05167e3b159e8475080005ccbf9b3bf92ea0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-assignment-operator.js": [
|
||||
"Deleted the 'x' math assignment",
|
||||
"Replaced '1' with '2' in the x math assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-assignment-operator.js"
|
||||
],
|
||||
"sha1": "641d05167e3b159e8475080005ccbf9b3bf92ea0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a5c2ac58b272f20910ed4aecae6f0effab2cca1b"
|
||||
}
|
||||
,{
|
||||
"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": "a5c2ac58b272f20910ed4aecae6f0effab2cca1b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2542f020646b9b5778e7ec7a0240b97bedd5818e"
|
||||
}
|
||||
,{
|
||||
"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": "2542f020646b9b5778e7ec7a0240b97bedd5818e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "17f5abea194c00c30becb942c3027e39e06587e5"
|
||||
}]
|
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": "7f626789377b5fd3eea7b354c6e5a1cc5fc2e265",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8ab55b9d82f1413aa9575f42f301dabd079db78c"
|
||||
}
|
||||
,{
|
||||
"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": "8ab55b9d82f1413aa9575f42f301dabd079db78c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4041641de1922c3898a8ee7cd196c558e7e69128"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-operator.js": [
|
||||
"Added the 'i + j * 3 - j % 5' math operator",
|
||||
"Deleted the 'i + j * 2 - j % 4' math operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-operator.js"
|
||||
],
|
||||
"sha1": "4041641de1922c3898a8ee7cd196c558e7e69128",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e8d325535d083a000ba8292202440a5495be8922"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-operator.js": [
|
||||
"Added the 'i + j * 2 - j % 4' math operator",
|
||||
"Deleted the 'i + j * 3 - j % 5' math operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-operator.js"
|
||||
],
|
||||
"sha1": "e8d325535d083a000ba8292202440a5495be8922",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9ca2993d5a9ace2a5028dff739736c6c39bae554"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-math-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"math-operator.js": [
|
||||
"Deleted the 'i + j * 2 - j % 4' math operator",
|
||||
"Replaced '3' with '2'",
|
||||
"Replaced '5' with '4'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"math-operator.js"
|
||||
],
|
||||
"sha1": "9ca2993d5a9ace2a5028dff739736c6c39bae554",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "dccbc9a4d8485e3a097694ccd115e42062a7722e"
|
||||
}
|
||||
,{
|
||||
"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": "dccbc9a4d8485e3a097694ccd115e42062a7722e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "56d97a6e44e0d8ce307d0830658fd81a25eb172e"
|
||||
}
|
||||
,{
|
||||
"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": "56d97a6e44e0d8ce307d0830658fd81a25eb172e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "431090fc86018346fe6fe6451088317d64412f5c"
|
||||
}]
|
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"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": "38c11bda6a55b3c21ca0223aeef09c65d9e19b9e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b46afa6e81c41a8e004dfe79ccdef1cd06e8f45c"
|
||||
}
|
||||
,{
|
||||
"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": "b46afa6e81c41a8e004dfe79ccdef1cd06e8f45c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0637e314252b495becd365b04d97b4b3bc0f5f7a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-assignment-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access-assignment.js": [
|
||||
"Added the 'y.x' assignment",
|
||||
"Deleted the 'y.x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access-assignment.js"
|
||||
],
|
||||
"sha1": "0637e314252b495becd365b04d97b4b3bc0f5f7a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "922e4ec1e5ae139002888cee60d3f0f5dfe6d9f3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-assignment-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access-assignment.js": [
|
||||
"Added the 'y.x' assignment",
|
||||
"Deleted the 'y.x' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access-assignment.js"
|
||||
],
|
||||
"sha1": "922e4ec1e5ae139002888cee60d3f0f5dfe6d9f3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b09d6ac57a7d20925f7281847609b263f2e68ee0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-assignment-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access-assignment.js": [
|
||||
"Deleted the 'y.x' assignment",
|
||||
"Replaced '0' with '1' in an assignment to y.x"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access-assignment.js"
|
||||
],
|
||||
"sha1": "b09d6ac57a7d20925f7281847609b263f2e68ee0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "83e944bd2dd963761c7b3196440edb39e23afbdb"
|
||||
}
|
||||
,{
|
||||
"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": "83e944bd2dd963761c7b3196440edb39e23afbdb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "58251cccc750ed5e7583893dff8081da214b7705"
|
||||
}
|
||||
,{
|
||||
"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": "58251cccc750ed5e7583893dff8081da214b7705",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "438f0f07b1217fbbc2a04a4d6ea1cf9d37ee0b2e"
|
||||
}]
|
123
test/corpus/diff-summaries/javascript/member-access.json
Normal file
123
test/corpus/diff-summaries/javascript/member-access.json
Normal file
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-member-access-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Added the 'x.someProperty' member access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "20a420167bbd93dbb126ff5173ccfea3f5b03a6c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8b07466f24185e81c7bf7f46757556a901ee7f7e"
|
||||
}
|
||||
,{
|
||||
"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": "8b07466f24185e81c7bf7f46757556a901ee7f7e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "03660c0a836773eb34b0535ca70d5c366446a184"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Added the 'x.someProperty' member access",
|
||||
"Deleted the 'x.someOtherProperty' member access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "03660c0a836773eb34b0535ca70d5c366446a184",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "84ab6054a45dc9a83f97fd3a76a252270fe4fdd6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Added the 'x.someOtherProperty' member access",
|
||||
"Deleted the 'x.someProperty' member access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "84ab6054a45dc9a83f97fd3a76a252270fe4fdd6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "159bebdd1458d0308c8a28d9ddbcdf376d19d332"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Deleted the 'x.someOtherProperty' member access",
|
||||
"Replaced the 'someProperty' identifier with the 'someOtherProperty' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "159bebdd1458d0308c8a28d9ddbcdf376d19d332",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5062c2847d21965b9d2078831d8b45972645c5f1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Deleted the 'x.someProperty' member access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "5062c2847d21965b9d2078831d8b45972645c5f1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e8579633ae9c5d08046191684f329ece4b9cd0f0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-member-access-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"member-access.js": [
|
||||
"Deleted the 'x.someOtherProperty' member access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"member-access.js"
|
||||
],
|
||||
"sha1": "e8579633ae9c5d08046191684f329ece4b9cd0f0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ab07812562da00039fe3b62e3a9bf575b1dc7559"
|
||||
}]
|
123
test/corpus/diff-summaries/javascript/method-call.json
Normal file
123
test/corpus/diff-summaries/javascript/method-call.json
Normal file
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"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": "82f873975d82ce87bb75e9b0aacf08b3b34834cd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1a1f5cf993a8ef32a497fa9313075a712b63afcf"
|
||||
}
|
||||
,{
|
||||
"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": "1a1f5cf993a8ef32a497fa9313075a712b63afcf",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c7cbead74a1da3d628c7877cd73d9cc9f71b1c3f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-method-call-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-call.js": [
|
||||
"Added the 'object.someMethod(arg1, \"arg2\")' method call",
|
||||
"Deleted the 'object.someMethod(arg1, \"arg3\")' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"method-call.js"
|
||||
],
|
||||
"sha1": "c7cbead74a1da3d628c7877cd73d9cc9f71b1c3f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ed615d306fbe046addb9f3d6c3eca761a892bc3b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-method-call-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-call.js": [
|
||||
"Added the 'object.someMethod(arg1, \"arg3\")' method call",
|
||||
"Deleted the 'object.someMethod(arg1, \"arg2\")' method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"method-call.js"
|
||||
],
|
||||
"sha1": "ed615d306fbe046addb9f3d6c3eca761a892bc3b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "86d4dbbb6082bc7b859733abb19e7d6051c20b9e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-method-call-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"method-call.js": [
|
||||
"Deleted the 'object.someMethod(arg1, \"arg3\")' method call",
|
||||
"Replaced the \"arg2\" string with the \"arg3\" string in the object.someMethod(arg1, \"arg3\") method call"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"method-call.js"
|
||||
],
|
||||
"sha1": "86d4dbbb6082bc7b859733abb19e7d6051c20b9e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f29faf035ddd260cc0454f31b23bfe9257e1f774"
|
||||
}
|
||||
,{
|
||||
"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": "f29faf035ddd260cc0454f31b23bfe9257e1f774",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9b202600ae89bffa76eeb7972227df3c46e24b16"
|
||||
}
|
||||
,{
|
||||
"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": "9b202600ae89bffa76eeb7972227df3c46e24b16",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2311700298627f011623e053dcffce4d08fb2fa5"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/named-function.json
Normal file
124
test/corpus/diff-summaries/javascript/named-function.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-named-function-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Added the 'myFunction' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "1bb9688393fd59b59ff2f59c16fae5e032ede0ac",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8e28e6cbd4437a3e81ad3442883c24a135895ed9"
|
||||
}
|
||||
,{
|
||||
"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": "8e28e6cbd4437a3e81ad3442883c24a135895ed9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7a448b82de63a0c6fd18fe27b32262cac4445af1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-named-function-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Added the 'myFunction' function",
|
||||
"Deleted the 'anotherFunction' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "7a448b82de63a0c6fd18fe27b32262cac4445af1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "7df7ffb6fc3d8b07ee69e1cdf2a93f89d06b6c8e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-named-function-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Added the 'anotherFunction' function",
|
||||
"Deleted the 'myFunction' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "7df7ffb6fc3d8b07ee69e1cdf2a93f89d06b6c8e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5b082012ac17f548a754eb6864cf915baa55bbf2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-named-function-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Deleted the 'anotherFunction' function",
|
||||
"Added the 'anotherFunction' function",
|
||||
"Deleted the 'myFunction' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "5b082012ac17f548a754eb6864cf915baa55bbf2",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ee4115150e100ee5013c1f3cb2177bebf3e913ea"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-named-function-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Deleted the 'myFunction' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "ee4115150e100ee5013c1f3cb2177bebf3e913ea",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4fd0d6233f7ebc39edcaa80f159aad8fdcf7a298"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-named-function-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"named-function.js": [
|
||||
"Deleted the 'anotherFunction' function"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"named-function.js"
|
||||
],
|
||||
"sha1": "4fd0d6233f7ebc39edcaa80f159aad8fdcf7a298",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "20a420167bbd93dbb126ff5173ccfea3f5b03a6c"
|
||||
}]
|
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": "33f99e8408e4e4651e7ae66d9f39efac529854de",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cdf8487c5d558f84bde177b8f7b7586aaddd6ac3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Added the 'null' return statement",
|
||||
"Added the 'null' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "cdf8487c5d558f84bde177b8f7b7586aaddd6ac3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "029fa839cfaf446dc6f08d447585eb564e5ee48e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Deleted the 'null' return statement",
|
||||
"Added the 'null' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "029fa839cfaf446dc6f08d447585eb564e5ee48e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b31696376e00e5c5e50a6e59407e25be64e21895"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Added the 'null' return statement",
|
||||
"Deleted the 'null' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "b31696376e00e5c5e50a6e59407e25be64e21895",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "833cbdb2559b151a261642fae1e54b19a605e510"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Deleted the 'null' return statement",
|
||||
"Added the 'null' return statement",
|
||||
"Deleted the 'null' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "833cbdb2559b151a261642fae1e54b19a605e510",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "85c6f2c73abaebdbeb599f9b9d6f5e4d6bcabc7b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Deleted the 'null' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "85c6f2c73abaebdbeb599f9b9d6f5e4d6bcabc7b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6be215e524a62a92d24835fcc840128bd34ce98e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-null-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"null.js": [
|
||||
"Deleted the 'null' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"null.js"
|
||||
],
|
||||
"sha1": "6be215e524a62a92d24835fcc840128bd34ce98e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3e74e70977a2c9089bafde685b74d385783018f3"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/number.json
Normal file
124
test/corpus/diff-summaries/javascript/number.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-number-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Added '101'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "9d9884eb636920bf593fc23a02ad4641b8ac8ab7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ece22bcf4b557cc96f48a4f20c9d7949094f49d6"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Added '102'",
|
||||
"Added '101'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "ece22bcf4b557cc96f48a4f20c9d7949094f49d6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "80eb161e398dae8576266801a2c55d7ca0c59613"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Added '101'",
|
||||
"Deleted '102'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "80eb161e398dae8576266801a2c55d7ca0c59613",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "825c74cea733a21d2035917cb86034ba5439167e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Added '102'",
|
||||
"Deleted '101'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "825c74cea733a21d2035917cb86034ba5439167e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "deb3d832e6aef2542280eaa3a99f20cd92f4d3e3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Deleted '102'",
|
||||
"Added '102'",
|
||||
"Deleted '101'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "deb3d832e6aef2542280eaa3a99f20cd92f4d3e3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8160871d5c50426b0130e496105eb9126f98bf41"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Deleted '101'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "8160871d5c50426b0130e496105eb9126f98bf41",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "227d27d24e72bd4f5d9ece88e6f1dc173f1b3bfb"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-number-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"number.js": [
|
||||
"Deleted '102'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"number.js"
|
||||
],
|
||||
"sha1": "227d27d24e72bd4f5d9ece88e6f1dc173f1b3bfb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4ffbee0b722bbcfc9f9b52a9dd03e89aca5fea7c"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/object-with-methods.json
Normal file
124
test/corpus/diff-summaries/javascript/object-with-methods.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-objects-with-methods-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Added the '{ add }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "133af9a2d6a65f9f341f5450f0c0155ba7aaa5df",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3ac968dd915ff4f32e7dc061c85a81466e583199"
|
||||
}
|
||||
,{
|
||||
"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": "3ac968dd915ff4f32e7dc061c85a81466e583199",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "45c872a9d2bb1992f6b47c0da9ad9521dbbdf6b9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-objects-with-methods-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Added the '{ add }' object",
|
||||
"Deleted the '{ subtract }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "45c872a9d2bb1992f6b47c0da9ad9521dbbdf6b9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ea32a9a4c57a89fe8757303b21c49a9695fb54f2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-objects-with-methods-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Added the '{ subtract }' object",
|
||||
"Deleted the '{ add }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "ea32a9a4c57a89fe8757303b21c49a9695fb54f2",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ab5707b9ddc401cb1485e81785e77095f57aa8fe"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-objects-with-methods-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Deleted the '{ subtract }' object",
|
||||
"Added the '{ subtract }' object",
|
||||
"Deleted the '{ add }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "ab5707b9ddc401cb1485e81785e77095f57aa8fe",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "64aba2b0d56f21d9a5642fafe707c1bc4322a3fd"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-objects-with-methods-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"objects-with-methods.js": [
|
||||
"Deleted the '{ add }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"objects-with-methods.js"
|
||||
],
|
||||
"sha1": "64aba2b0d56f21d9a5642fafe707c1bc4322a3fd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5f09d5d470328401cb7f5b1ec4ed89435a2ed91e"
|
||||
}
|
||||
,{
|
||||
"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": "5f09d5d470328401cb7f5b1ec4ed89435a2ed91e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ab6a9bd2d5a2b7509e21e09bfcbd5a85291bf03c"
|
||||
}]
|
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": "42568766bb733eed07b52ce1e60228d6ca7b9b3d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b41b2d7a4696d1a9d87dbd741cbd5be43be267e9"
|
||||
}
|
||||
,{
|
||||
"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": "b41b2d7a4696d1a9d87dbd741cbd5be43be267e9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bce59fe5bf8a1ebe039cb15c8891279c08d71623"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-object-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Added the '{ \"key1\": … }' object",
|
||||
"Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "bce59fe5bf8a1ebe039cb15c8891279c08d71623",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "30990ba3e9fafa9a9327f12c00c5fdf4f65299d4"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-object-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object",
|
||||
"Deleted the '{ \"key1\": … }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "30990ba3e9fafa9a9327f12c00c5fdf4f65299d4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3eb8a70412a2dd5619e447555d26906238361198"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-object-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object",
|
||||
"Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object",
|
||||
"Deleted the '{ \"key1\": … }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "3eb8a70412a2dd5619e447555d26906238361198",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "29ccc323daa318c1a76240ce58f512640b42212f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-object-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Deleted the '{ \"key1\": … }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "29ccc323daa318c1a76240ce58f512640b42212f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "772e2957a5c9e07366553203c493f2bcd1d36c89"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-object-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"object.js": [
|
||||
"Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"object.js"
|
||||
],
|
||||
"sha1": "772e2957a5c9e07366553203c493f2bcd1d36c89",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e8b2b7fe36d673849485d794fb1cbd70190d690d"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/regex.json
Normal file
124
test/corpus/diff-summaries/javascript/regex.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-regex-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Added the '/one/g' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "1670fd7f152a029473809cef155bf0af94fd59e6",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a013c3c87cdf4e7580d77e25f2cee19ad57fec20"
|
||||
}
|
||||
,{
|
||||
"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": "a013c3c87cdf4e7580d77e25f2cee19ad57fec20",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e0da7100b5fc22a7d4758b58780a0f6c33bdfe45"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-regex-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Added the '/one/g' regex",
|
||||
"Deleted the '/on[^/]afe/gim' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "e0da7100b5fc22a7d4758b58780a0f6c33bdfe45",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "58820f578badc901a2196d9c3e98a63231c3c813"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-regex-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Added the '/on[^/]afe/gim' regex",
|
||||
"Deleted the '/one/g' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "58820f578badc901a2196d9c3e98a63231c3c813",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b7ec6b3b0cbfac67762aa17db475a6f38c598994"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-regex-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Deleted the '/on[^/]afe/gim' regex",
|
||||
"Added the '/on[^/]afe/gim' regex",
|
||||
"Deleted the '/one/g' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "b7ec6b3b0cbfac67762aa17db475a6f38c598994",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ee4cceca23be158acd6a47d8372110ae541d1e7d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-regex-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Deleted the '/one/g' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "ee4cceca23be158acd6a47d8372110ae541d1e7d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a4292be29c133bbd8da9f581ae4d26ce13826f40"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-regex-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.js": [
|
||||
"Deleted the '/on[^/]afe/gim' regex"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.js"
|
||||
],
|
||||
"sha1": "a4292be29c133bbd8da9f581ae4d26ce13826f40",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "fcbc798fe671ee47690ed91b7645bbd2be9cd7eb"
|
||||
}]
|
@ -0,0 +1,86 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-relational-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"relational-operator.js": [
|
||||
"Added the 'x < y' relational operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"relational-operator.js"
|
||||
],
|
||||
"sha1": "2b3a648ff2420e7e577c6ac2909dfdf09ec6d3bd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "acb0990543bb7df4fc817d7dd00bb2f573148565"
|
||||
}
|
||||
,{
|
||||
"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": "acb0990543bb7df4fc817d7dd00bb2f573148565",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ad46656407f725ac32983a8271c0efc20eb3db37"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-relational-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"relational-operator.js": [
|
||||
"Deleted the 'x < y' relational operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"relational-operator.js"
|
||||
],
|
||||
"sha1": "97ddfebb00c70ab04f760ed922c7f1e6ae052a7b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b2f4c7a5732f1643ec4e44a699131252eb2625b7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-relational-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"relational-operator.js": [
|
||||
"Deleted the 'x <= y' relational operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"relational-operator.js"
|
||||
],
|
||||
"sha1": "b2f4c7a5732f1643ec4e44a699131252eb2625b7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e8492c45be33305d253a9e88ddb2624200ff2cbc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-relational-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"relational-operator.js": [
|
||||
"Deleted the 'x <= y' relational operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"relational-operator.js"
|
||||
],
|
||||
"sha1": "e8492c45be33305d253a9e88ddb2624200ff2cbc",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "fed990263904999ef2b80934ed1a3881d7cf7056"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/return-statement.json
Normal file
124
test/corpus/diff-summaries/javascript/return-statement.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-return-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Added the '5' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "66eecf807ba1e2964d6937be2095ef24a1676269",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2f83da1cff87e975d21351f8cce6e819ebbb9f33"
|
||||
}
|
||||
,{
|
||||
"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": "2f83da1cff87e975d21351f8cce6e819ebbb9f33",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d8ecdffd002b056579fc5aeccf8c62e4267f13b3"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-return-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Added the '5' return statement",
|
||||
"Deleted the 'empty' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "d8ecdffd002b056579fc5aeccf8c62e4267f13b3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3d2026e2cb6789ebe899e82b9912844a53b0720a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-return-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Added the 'empty' return statement",
|
||||
"Deleted the '5' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "3d2026e2cb6789ebe899e82b9912844a53b0720a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "93a90e3df5860ca22d377db9b4d2a1ad9aebc0db"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-return-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Deleted the 'empty' return statement",
|
||||
"Added the 'empty' return statement",
|
||||
"Deleted the '5' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "93a90e3df5860ca22d377db9b4d2a1ad9aebc0db",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "03875cdd139a3151cfbb1e992d18aa9ed2c73bf9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-return-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Deleted the '5' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "03875cdd139a3151cfbb1e992d18aa9ed2c73bf9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9590e51df3ff791b4060312b7b325d2ac1eedefa"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-return-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"return-statement.js": [
|
||||
"Deleted the 'empty' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"return-statement.js"
|
||||
],
|
||||
"sha1": "9590e51df3ff791b4060312b7b325d2ac1eedefa",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5099a9bb7a28ce5fe5558ce9c69813cb91a62ac1"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/string.json
Normal file
124
test/corpus/diff-summaries/javascript/string.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"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": "ab6a9bd2d5a2b7509e21e09bfcbd5a85291bf03c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "068c2d089209d0b5f0db6a679fa5f4eed82f14c2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-string-replacement-insert-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",
|
||||
"Added 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": "068c2d089209d0b5f0db6a679fa5f4eed82f14c2",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "40453fc4124883da03a9193b4d22ef74461a3960"
|
||||
}
|
||||
,{
|
||||
"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": "40453fc4124883da03a9193b4d22ef74461a3960",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "24c2da4cae52472aca75441afc918a0cc90d0bf7"
|
||||
}
|
||||
,{
|
||||
"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": "24c2da4cae52472aca75441afc918a0cc90d0bf7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "50b61d150a7dcbb60b29de0ad56e17ae1c0e9acb"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-string-delete-replacement-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",
|
||||
"Replaced the 'A string with \"double\" quotes' at line 1, column 0 - line 1, column 29 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 2, column 0 - line 2, column 29 in string.js"
|
||||
]
|
||||
}
|
||||
},
|
||||
"filePaths": [
|
||||
"string.js"
|
||||
],
|
||||
"sha1": "50b61d150a7dcbb60b29de0ad56e17ae1c0e9acb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e428a1ce47716442b626a48d1bff3a1424205d56"
|
||||
}
|
||||
,{
|
||||
"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": "e428a1ce47716442b626a48d1bff3a1424205d56",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b4df392490b48828a0e8e7fad317fd6ab695460e"
|
||||
}
|
||||
,{
|
||||
"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": "b4df392490b48828a0e8e7fad317fd6ab695460e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9d9884eb636920bf593fc23a02ad4641b8ac8ab7"
|
||||
}]
|
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"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": "438f0f07b1217fbbc2a04a4d6ea1cf9d37ee0b2e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4a77536a5a70253856c63f564b8df759cf52ba97"
|
||||
}
|
||||
,{
|
||||
"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": "4a77536a5a70253856c63f564b8df759cf52ba97",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3aa38e80a1ee05ce9e02ab51c692d596f6ac5905"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-assignment.js": [
|
||||
"Added the 'y[\"x\"]' assignment",
|
||||
"Deleted the 'y[\"x\"]' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-assignment.js"
|
||||
],
|
||||
"sha1": "3aa38e80a1ee05ce9e02ab51c692d596f6ac5905",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b1de0aad6422986bc93215d3d7c1dbb3fa1f3b0e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-assignment-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-assignment.js": [
|
||||
"Added the 'y[\"x\"]' assignment",
|
||||
"Deleted the 'y[\"x\"]' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-assignment.js"
|
||||
],
|
||||
"sha1": "b1de0aad6422986bc93215d3d7c1dbb3fa1f3b0e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ac11c73219907ccdff69306d04f0b5db00f72181"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-assignment.js": [
|
||||
"Deleted the 'y[\"x\"]' assignment",
|
||||
"Replaced '0' with '1' in an assignment to y[\"x\"]"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-assignment.js"
|
||||
],
|
||||
"sha1": "ac11c73219907ccdff69306d04f0b5db00f72181",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "db05947b1614397d9a0a75d37a969eebb783db52"
|
||||
}
|
||||
,{
|
||||
"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": "db05947b1614397d9a0a75d37a969eebb783db52",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0e89feddc990fb40fcaa37ca09bdd23dbc0aee51"
|
||||
}
|
||||
,{
|
||||
"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": "0e89feddc990fb40fcaa37ca09bdd23dbc0aee51",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8e9465a057e544de7926bfee045371e151262b37"
|
||||
}]
|
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"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": "90219bef77675f7798d2eca6fe534c4efe2fc76d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "abbd81079971f3fba22d7cce5c129ba49322159e"
|
||||
}
|
||||
,{
|
||||
"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": "abbd81079971f3fba22d7cce5c129ba49322159e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e47760d1a32b29b95daef26509d2e94197f6eb03"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-string-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-string.js": [
|
||||
"Added the 'x[\"some-string\"]' subscript access",
|
||||
"Deleted the 'x[\"some-other-string\"]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-string.js"
|
||||
],
|
||||
"sha1": "e47760d1a32b29b95daef26509d2e94197f6eb03",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3bec91560ae76a5112e3011b616e8144430721ae"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-string-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-string.js": [
|
||||
"Added the 'x[\"some-other-string\"]' subscript access",
|
||||
"Deleted the 'x[\"some-string\"]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-string.js"
|
||||
],
|
||||
"sha1": "3bec91560ae76a5112e3011b616e8144430721ae",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "97ddd7b7f13ceb96df8c3cd12d6b20afc4c6821e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-string-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-string.js": [
|
||||
"Deleted the 'x[\"some-other-string\"]' subscript access",
|
||||
"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": "97ddd7b7f13ceb96df8c3cd12d6b20afc4c6821e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "de6b1543ed915f74bf49aa9ce3a97ea44c3333e9"
|
||||
}
|
||||
,{
|
||||
"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": "de6b1543ed915f74bf49aa9ce3a97ea44c3333e9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f5febc4895be2e0634d97c05deb8763892b3580e"
|
||||
}
|
||||
,{
|
||||
"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": "f5febc4895be2e0634d97c05deb8763892b3580e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0d39978593de2568f3ab5b0db632c7091f305835"
|
||||
}]
|
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"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": "ab07812562da00039fe3b62e3a9bf575b1dc7559",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "412460ccd9d4a7a83235c7cdef21e5f42eac7f2d"
|
||||
}
|
||||
,{
|
||||
"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": "412460ccd9d4a7a83235c7cdef21e5f42eac7f2d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "93ac1ae7a3096e7e96a506bb40cfc28246cf8e5a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-variable-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-variable.js": [
|
||||
"Added the 'x[someVariable]' subscript access",
|
||||
"Deleted the 'x[someOtherVariable]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-variable.js"
|
||||
],
|
||||
"sha1": "93ac1ae7a3096e7e96a506bb40cfc28246cf8e5a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "8097694c4750a0208a8737a0648497d24606f309"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-variable-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-variable.js": [
|
||||
"Added the 'x[someOtherVariable]' subscript access",
|
||||
"Deleted the 'x[someVariable]' subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-variable.js"
|
||||
],
|
||||
"sha1": "8097694c4750a0208a8737a0648497d24606f309",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d66e9bd9493f41fb603c23ca1751d93ce392fdf1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"subscript-access-variable.js": [
|
||||
"Deleted the 'x[someOtherVariable]' subscript access",
|
||||
"Replaced the 'someVariable' identifier with the 'someOtherVariable' identifier in the x[someOtherVariable] subscript access"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"subscript-access-variable.js"
|
||||
],
|
||||
"sha1": "d66e9bd9493f41fb603c23ca1751d93ce392fdf1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e22de68c8ceade38069939c68d37caff9aa70900"
|
||||
}
|
||||
,{
|
||||
"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": "e22de68c8ceade38069939c68d37caff9aa70900",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a8fb624306d17ef5c1e8716f086fa55a4bfe3ae5"
|
||||
}
|
||||
,{
|
||||
"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": "a8fb624306d17ef5c1e8716f086fa55a4bfe3ae5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "90219bef77675f7798d2eca6fe534c4efe2fc76d"
|
||||
}]
|
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": "5b6687475c3b7f8c43a128b52e6c4e9220558a04",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "0e588dcc415c6ee6f0ac3182c27869e656d26372"
|
||||
}
|
||||
,{
|
||||
"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": "0e588dcc415c6ee6f0ac3182c27869e656d26372",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "74b39c4f997dc2bdc3b921a6c00e1f00ddc3222c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-switch-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Deleted the '2' switch statement",
|
||||
"Added the '1' switch statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "74b39c4f997dc2bdc3b921a6c00e1f00ddc3222c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f3ab8d479c68038ee139c1c1ef92943fbeabcbf7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-switch-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Added the '2' switch statement",
|
||||
"Deleted the '1' switch statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "f3ab8d479c68038ee139c1c1ef92943fbeabcbf7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9160877730ddc36b3ed036c9599ab233dc0a6ec7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-switch-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Deleted the '2' switch statement",
|
||||
"Added the '2' switch statement",
|
||||
"Deleted the '1' switch statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "9160877730ddc36b3ed036c9599ab233dc0a6ec7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3fa146d5da730e55b903d214d1b4bed48fb7cac8"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-switch-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Deleted the '1' switch statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "3fa146d5da730e55b903d214d1b4bed48fb7cac8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "69f8f27e8975e8e1f550f3d6eb2db8c2726810d8"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-switch-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"switch-statement.js": [
|
||||
"Deleted the '2' switch statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"switch-statement.js"
|
||||
],
|
||||
"sha1": "69f8f27e8975e8e1f550f3d6eb2db8c2726810d8",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2ffbc093aa5e7fb91f1dc158a74fd7f9260bc51c"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/template-string.json
Normal file
124
test/corpus/diff-summaries/javascript/template-string.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-template-string-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"template-string.js": [
|
||||
"Added the '`one line`' template string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"template-string.js"
|
||||
],
|
||||
"sha1": "82ac9049dc6dcbfef96c1c8c65501872466b44fb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "30d0936143b14b2d0e439300e5ef643315046887"
|
||||
}
|
||||
,{
|
||||
"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": "30d0936143b14b2d0e439300e5ef643315046887",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "699391b454f168a1eab35358bd1cf1a530bbf420"
|
||||
}
|
||||
,{
|
||||
"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": "699391b454f168a1eab35358bd1cf1a530bbf420",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b51c70761a973ea900d4b25a8f8b4ee662b76760"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-template-string-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"template-string.js": [
|
||||
"Added the '`multi line`' template string",
|
||||
"Deleted the '`one line`' template string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"template-string.js"
|
||||
],
|
||||
"sha1": "b51c70761a973ea900d4b25a8f8b4ee662b76760",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f78f831fb49f207742537af6dfe28ae402f783ce"
|
||||
}
|
||||
,{
|
||||
"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": "f78f831fb49f207742537af6dfe28ae402f783ce",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "498cb72499d1f739e3a8a465049b5f0860fca989"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-template-string-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"template-string.js": [
|
||||
"Deleted the '`one line`' template string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"template-string.js"
|
||||
],
|
||||
"sha1": "498cb72499d1f739e3a8a465049b5f0860fca989",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a6b6a5b162e47aa8fe57774c3edb48547c2144e7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-template-string-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"template-string.js": [
|
||||
"Deleted the '`multi line`' template string"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"template-string.js"
|
||||
],
|
||||
"sha1": "a6b6a5b162e47aa8fe57774c3edb48547c2144e7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "a49b3cc79bf0a423e6474f02d4f9b2deae2cf7aa"
|
||||
}]
|
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": "b4a653f9eafddd6ddabce75bab6f1de384618add",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "925e3e564cd9943e7b96d1bb57193e3050ece024"
|
||||
}
|
||||
,{
|
||||
"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": "925e3e564cd9943e7b96d1bb57193e3050ece024",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ce72bab3cb389e21cf70ed5aa6200f7704015da0"
|
||||
}
|
||||
,{
|
||||
"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": "ce72bab3cb389e21cf70ed5aa6200f7704015da0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6ce7e2699e1ac1736eac9e4dd9af02599f17409f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-ternary-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"ternary.js": [
|
||||
"Added the 'x.y' assignment",
|
||||
"Deleted the 'condition' ternary expression"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"ternary.js"
|
||||
],
|
||||
"sha1": "6ce7e2699e1ac1736eac9e4dd9af02599f17409f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6ea41971a6960f5661fb063aaeeb29723e984011"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-ternary-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"ternary.js": [
|
||||
"Deleted the 'x.y' assignment",
|
||||
"Added the 'x.y' assignment",
|
||||
"Deleted the 'condition' ternary expression"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"ternary.js"
|
||||
],
|
||||
"sha1": "6ea41971a6960f5661fb063aaeeb29723e984011",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "3ef7357faaaeca2e364d36088053337c2b16d288"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-ternary-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"ternary.js": [
|
||||
"Deleted the 'condition' ternary expression"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"ternary.js"
|
||||
],
|
||||
"sha1": "3ef7357faaaeca2e364d36088053337c2b16d288",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4b1b651e923d6690b014e1ec17ef0ebb883b015b"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-ternary-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"ternary.js": [
|
||||
"Deleted the 'x.y' assignment"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"ternary.js"
|
||||
],
|
||||
"sha1": "4b1b651e923d6690b014e1ec17ef0ebb883b015b",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "85cdcb0ca5be731d1cd601c0640dae4713b4b2e3"
|
||||
}]
|
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": "d50748ed7b3cffe454cf051e79a391b70cb1f55d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5a3ed73dc7f583c5d52ee08edb75c381d7ef52d7"
|
||||
}
|
||||
,{
|
||||
"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": "5a3ed73dc7f583c5d52ee08edb75c381d7ef52d7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d3fe93b8b10c2c6d052a569bdd2001b582596ca2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-this-expression-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"this-expression.js": [
|
||||
"Deleted the 'this' return statement",
|
||||
"Added the 'this' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"this-expression.js"
|
||||
],
|
||||
"sha1": "d3fe93b8b10c2c6d052a569bdd2001b582596ca2",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4433219c7827604a4bc803d1bbbb76f8abee643e"
|
||||
}
|
||||
,{
|
||||
"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": "4433219c7827604a4bc803d1bbbb76f8abee643e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "800d50cac37be657144a55d5f35f6b89cc115b57"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-this-expression-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"this-expression.js": [
|
||||
"Deleted the 'this' return statement",
|
||||
"Added the 'this' return statement",
|
||||
"Deleted the 'this' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"this-expression.js"
|
||||
],
|
||||
"sha1": "800d50cac37be657144a55d5f35f6b89cc115b57",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "baf032e0f50f00f575036eaf589a91ff85268b00"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-this-expression-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"this-expression.js": [
|
||||
"Deleted the 'this' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"this-expression.js"
|
||||
],
|
||||
"sha1": "baf032e0f50f00f575036eaf589a91ff85268b00",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b0151344a8cdf29ab8a22a0b3b74023032dac75e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-this-expression-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"this-expression.js": [
|
||||
"Deleted the 'this' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"this-expression.js"
|
||||
],
|
||||
"sha1": "b0151344a8cdf29ab8a22a0b3b74023032dac75e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "33f99e8408e4e4651e7ae66d9f39efac529854de"
|
||||
}]
|
125
test/corpus/diff-summaries/javascript/throw-statement.json
Normal file
125
test/corpus/diff-summaries/javascript/throw-statement.json
Normal file
@ -0,0 +1,125 @@
|
||||
[{
|
||||
"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": "2ffbc093aa5e7fb91f1dc158a74fd7f9260bc51c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "21ee5f7afe05a4ab0a2269c92f801575d71e8071"
|
||||
}
|
||||
,{
|
||||
"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": "21ee5f7afe05a4ab0a2269c92f801575d71e8071",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5b29f7a80db0838b538c457a8616cc42ac5e1384"
|
||||
}
|
||||
,{
|
||||
"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": "5b29f7a80db0838b538c457a8616cc42ac5e1384",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e3cedef9bf3366041a1fae7cde30ea0d27007dea"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-throw-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"throw-statement.js": [
|
||||
"Added the 'new Error(\"oooooops\")' throw statement",
|
||||
"Added the 'new Error(\"uh oh\")' throw statement",
|
||||
"Deleted the 'new Error(\"uh oh\")' throw statement",
|
||||
"Deleted the 'new Error(\"uh oh\")' throw statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"throw-statement.js"
|
||||
],
|
||||
"sha1": "e3cedef9bf3366041a1fae7cde30ea0d27007dea",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "15ae18a4233211f58fbd7e792eab8994c6a48646"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-throw-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"throw-statement.js": [
|
||||
"Added the 'new Error(\"uh oh\")' throw statement",
|
||||
"Deleted the 'new Error(\"uh oh\")' throw statement",
|
||||
"Deleted the 'new Error(\"uh oh\")' throw statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"throw-statement.js"
|
||||
],
|
||||
"sha1": "15ae18a4233211f58fbd7e792eab8994c6a48646",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ae1127c99b71527c190f3c09449d7d8fc72fc4ac"
|
||||
}
|
||||
,{
|
||||
"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": "ae1127c99b71527c190f3c09449d7d8fc72fc4ac",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ab76eb0cff6136de1fcf638d226dab9717c95f71"
|
||||
}
|
||||
,{
|
||||
"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": "ab76eb0cff6136de1fcf638d226dab9717c95f71",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "63fd3426061563d57feb9002166fed202ef61781"
|
||||
}]
|
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": "d7e78ffcadb2e3594640d8df159206ccdcf30614",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "403119b24151036bf00fe40610060b9b78bca0e4"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Added the 'true' return statement",
|
||||
"Added 'true'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "403119b24151036bf00fe40610060b9b78bca0e4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "426d5721b9648b2685fe184f0d33fa3f8fc970d1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Deleted the 'true' return statement",
|
||||
"Added 'true'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "426d5721b9648b2685fe184f0d33fa3f8fc970d1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "02e5dbd8227597aab0fe3ae48602af3ac2e8c574"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Added the 'true' return statement",
|
||||
"Deleted 'true'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "02e5dbd8227597aab0fe3ae48602af3ac2e8c574",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "07162e4f6230106238ce1c824210ad24f038cda4"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Deleted the 'true' return statement",
|
||||
"Added the 'true' return statement",
|
||||
"Deleted 'true'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "07162e4f6230106238ce1c824210ad24f038cda4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "4ec6dde73f341c4279f848466fe2fcb4ea48e708"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Deleted 'true'"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "4ec6dde73f341c4279f848466fe2fcb4ea48e708",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e255f8e05b11954d646414b9b5a69ce8ca2edbf2"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-true-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"true.js": [
|
||||
"Deleted the 'true' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"true.js"
|
||||
],
|
||||
"sha1": "e255f8e05b11954d646414b9b5a69ce8ca2edbf2",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cbcf093735696437716562b80be6c19a66e585c0"
|
||||
}]
|
126
test/corpus/diff-summaries/javascript/try-statement.json
Normal file
126
test/corpus/diff-summaries/javascript/try-statement.json
Normal file
@ -0,0 +1,126 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-try-statement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Added the '{ f; }' try statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "63fd3426061563d57feb9002166fed202ef61781",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "893cd8c62c644898fc53032a8a0692d0c7a0a965"
|
||||
}
|
||||
,{
|
||||
"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": "893cd8c62c644898fc53032a8a0692d0c7a0a965",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c505a47a3161f53427e908b46f1dd56af37cee65"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-try-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Deleted the '{ f; }' try statement",
|
||||
"Added the '{ f; }' try statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "c505a47a3161f53427e908b46f1dd56af37cee65",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c9b19aefc1a5b0680f0344912ebc73ca39ab6ab7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-try-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Added the '{ f; }' try statement",
|
||||
"Added the '{ f; }' try statement",
|
||||
"Deleted the '{ f; }' try statement",
|
||||
"Deleted the '{ f; }' try statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "c9b19aefc1a5b0680f0344912ebc73ca39ab6ab7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1b08ba78dcd997dc523a669ac82f65e797dd1ad0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-try-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Deleted the '{ f; }' try statement",
|
||||
"Added the '{ f; }' try statement",
|
||||
"Deleted the '{ f; }' try statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "1b08ba78dcd997dc523a669ac82f65e797dd1ad0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c281dd1f1255e7207d7fa281aa1c1f62f05f5cd0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-try-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Deleted the '{ f; }' try statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "c281dd1f1255e7207d7fa281aa1c1f62f05f5cd0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "72dabce1dd7ff8c444a2e52c9ea9a359fb993382"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-try-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"try-statement.js": [
|
||||
"Deleted the '{ f; }' try statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"try-statement.js"
|
||||
],
|
||||
"sha1": "72dabce1dd7ff8c444a2e52c9ea9a359fb993382",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1670fd7f152a029473809cef155bf0af94fd59e6"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/type-operator.json
Normal file
124
test/corpus/diff-summaries/javascript/type-operator.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-type-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Added the 'typeof x' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "85cdcb0ca5be731d1cd601c0640dae4713b4b2e3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "6f3fef4632c21cb6b38a3dcba7c32eff0974fdc5"
|
||||
}
|
||||
,{
|
||||
"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": "6f3fef4632c21cb6b38a3dcba7c32eff0974fdc5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cac5ff4597d575ece0780d1d729ab0816aea317e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-type-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Added the 'typeof x' operator",
|
||||
"Deleted the 'x instanceof String' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "cac5ff4597d575ece0780d1d729ab0816aea317e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "84bd53fb47869270edeeb9c837bced5bd5a9010d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-type-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Added the 'x instanceof String' operator",
|
||||
"Deleted the 'typeof x' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "84bd53fb47869270edeeb9c837bced5bd5a9010d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "21b00bf7d0f121619a4217b64a42ace62d6d9c60"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-type-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Deleted the 'x instanceof String' operator",
|
||||
"Added the 'x instanceof String' operator",
|
||||
"Deleted the 'typeof x' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "21b00bf7d0f121619a4217b64a42ace62d6d9c60",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "faf8e8a4188d3b1f4c207d6c03f50e11d63438a9"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-type-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Deleted the 'typeof x' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "faf8e8a4188d3b1f4c207d6c03f50e11d63438a9",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "318e72aa757b15215d5dfeb20c725c5453ce7712"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-type-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"type-operator.js": [
|
||||
"Deleted the 'x instanceof String' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"type-operator.js"
|
||||
],
|
||||
"sha1": "318e72aa757b15215d5dfeb20c725c5453ce7712",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bc15aec1c4c4587cd5b4d204e3f00feec92121dc"
|
||||
}]
|
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": "3e74e70977a2c9089bafde685b74d385783018f3",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d3e7f0bbf596af56e82a57dbd47fee7d2eeef770"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Added the 'undefined' return statement",
|
||||
"Added the 'undefined' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "d3e7f0bbf596af56e82a57dbd47fee7d2eeef770",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "412a8264cd76e82efb3a3f11807adc3674b59619"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Deleted the 'undefined' return statement",
|
||||
"Added the 'undefined' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "412a8264cd76e82efb3a3f11807adc3674b59619",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e611d8496e7cddedd027f74f89ee82c0b6cab130"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Added the 'undefined' return statement",
|
||||
"Deleted the 'undefined' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "e611d8496e7cddedd027f74f89ee82c0b6cab130",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "132fa390f92fad660e984ad37acb034966726dc5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Deleted the 'undefined' return statement",
|
||||
"Added the 'undefined' return statement",
|
||||
"Deleted the 'undefined' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "132fa390f92fad660e984ad37acb034966726dc5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1a0c2c6600f9031a199c35cda40897634eb8f7d0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Deleted the 'undefined' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "1a0c2c6600f9031a199c35cda40897634eb8f7d0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bf88d34a356e87c27b6ccadaa38ba99204057855"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-undefined-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"undefined.js": [
|
||||
"Deleted the 'undefined' return statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"undefined.js"
|
||||
],
|
||||
"sha1": "bf88d34a356e87c27b6ccadaa38ba99204057855",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "d7e78ffcadb2e3594640d8df159206ccdcf30614"
|
||||
}]
|
136
test/corpus/diff-summaries/javascript/var-declaration.json
Normal file
136
test/corpus/diff-summaries/javascript/var-declaration.json
Normal file
@ -0,0 +1,136 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-var-declaration-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Added the 'x' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "5099a9bb7a28ce5fe5558ce9c69813cb91a62ac1",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "cfc3d6557f320bbb7e8c5b5fc9820db038bc2745"
|
||||
}
|
||||
,{
|
||||
"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": "cfc3d6557f320bbb7e8c5b5fc9820db038bc2745",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "df50d8c3f4cc74a89cd0002dc42347a2c0c493ce"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-var-declaration-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Deleted the 'x' variable",
|
||||
"Deleted the 'y' variable",
|
||||
"Deleted the 'z' variable",
|
||||
"Added the 'x' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "df50d8c3f4cc74a89cd0002dc42347a2c0c493ce",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2397f594fe9a2f64c9d9b020e3887e464b988069"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-var-declaration-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Added the 'x' variable",
|
||||
"Added the 'y' variable",
|
||||
"Added the 'z' variable",
|
||||
"Deleted the 'x' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "2397f594fe9a2f64c9d9b020e3887e464b988069",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "557258b247d3bc49b25f3213f42043b129511677"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-var-declaration-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Deleted the 'x' variable",
|
||||
"Deleted the 'y' variable",
|
||||
"Deleted the 'z' variable",
|
||||
"Added the 'x' variable",
|
||||
"Added the 'y' variable",
|
||||
"Added the 'z' variable",
|
||||
"Deleted the 'x' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "557258b247d3bc49b25f3213f42043b129511677",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "b7d9d5c8847f99999a0d2136e592482db7a647b0"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-var-declaration-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"var-declaration.js": [
|
||||
"Deleted the 'x' variable"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"var-declaration.js"
|
||||
],
|
||||
"sha1": "b7d9d5c8847f99999a0d2136e592482db7a647b0",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "42e244fcd70a9dc599ab8a0031d2320e832ea0fe"
|
||||
}
|
||||
,{
|
||||
"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": "42e244fcd70a9dc599ab8a0031d2320e832ea0fe",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "c367cef2a2ab4f6c19c197ff79c0e633b62e30b4"
|
||||
}]
|
123
test/corpus/diff-summaries/javascript/variable.json
Normal file
123
test/corpus/diff-summaries/javascript/variable.json
Normal file
@ -0,0 +1,123 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-variable-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Added the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "4ffbee0b722bbcfc9f9b52a9dd03e89aca5fea7c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "51c88e75a16178808c46ec33cb95c6aace91a5ba"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Added the 'theVar2' identifier",
|
||||
"Added the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "51c88e75a16178808c46ec33cb95c6aace91a5ba",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1f94cc9b8313d60de7b3f266ca068de340e40791"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Added the 'theVar' identifier",
|
||||
"Deleted the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "1f94cc9b8313d60de7b3f266ca068de340e40791",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "45d901f0e787a9b326b0cedce5d54106b402c02f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Added the 'theVar2' identifier",
|
||||
"Deleted the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "45d901f0e787a9b326b0cedce5d54106b402c02f",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ae17407e97565ded44edbf19ece47699da4a968a"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Deleted the 'theVar2' identifier",
|
||||
"Replaced the 'theVar' identifier with the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "ae17407e97565ded44edbf19ece47699da4a968a",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "1f515b44a4103591f92b87ad78790151646b74e7"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Deleted the 'theVar' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "1f515b44a4103591f92b87ad78790151646b74e7",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e57e0883f17c0132d8ef173b14aef230ccf9bd52"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-variable-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"variable.js": [
|
||||
"Deleted the 'theVar2' identifier"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"variable.js"
|
||||
],
|
||||
"sha1": "e57e0883f17c0132d8ef173b14aef230ccf9bd52",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "f956fe4ea44f5d38071a3c8a5a5342259ff9bb28"
|
||||
}]
|
124
test/corpus/diff-summaries/javascript/void-operator.json
Normal file
124
test/corpus/diff-summaries/javascript/void-operator.json
Normal file
@ -0,0 +1,124 @@
|
||||
[{
|
||||
"testCaseDescription": "javascript-void-operator-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Added the 'void b()' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "0e5929ffe5c88dd824b05f48b9025ccfa67f9c04",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "330dbfd3ac17128d8b9f89c09b0a98b4632f4b07"
|
||||
}
|
||||
,{
|
||||
"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": "330dbfd3ac17128d8b9f89c09b0a98b4632f4b07",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5bec467955db5f992fda247e6adf08d6a77c15e4"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-void-operator-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Added the 'void b()' operator",
|
||||
"Deleted the 'void c()' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "5bec467955db5f992fda247e6adf08d6a77c15e4",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "16aa9a553cf8b14a5900a4f10a5c9ddc60a03f2e"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-void-operator-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Added the 'void c()' operator",
|
||||
"Deleted the 'void b()' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "16aa9a553cf8b14a5900a4f10a5c9ddc60a03f2e",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "50dad24e865c00cf6fb3bfb45e08f05670eadb0c"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-void-operator-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Deleted the 'void c()' operator",
|
||||
"Added the 'void c()' operator",
|
||||
"Deleted the 'void b()' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "50dad24e865c00cf6fb3bfb45e08f05670eadb0c",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5fd24c7b556fb462c4c8ac55cb04acb69ca54cfa"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-void-operator-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Deleted the 'void b()' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "5fd24c7b556fb462c4c8ac55cb04acb69ca54cfa",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "e406f99aa288ecc7a90f808cd78fde9b034d1dbb"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-void-operator-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"void-operator.js": [
|
||||
"Deleted the 'void c()' operator"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"void-operator.js"
|
||||
],
|
||||
"sha1": "e406f99aa288ecc7a90f808cd78fde9b034d1dbb",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "5c0c3689340b3b739532d2312d2eb95be94926ce"
|
||||
}]
|
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": "b8093b25382e8511330d32163f647d8091652050",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "bea2e77bfc7f83db9b780b82746288e89f4fa9ac"
|
||||
}
|
||||
,{
|
||||
"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": "bea2e77bfc7f83db9b780b82746288e89f4fa9ac",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "18fa25d4a351498ec940d1af49b60c5551ab92c5"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-while-statement-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Deleted the 'b' while statement",
|
||||
"Added the 'a' while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "18fa25d4a351498ec940d1af49b60c5551ab92c5",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "2881e3bbde88d23cdea2693f780005b3909719ca"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-while-statement-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Added the 'b' while statement",
|
||||
"Deleted the 'a' while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "2881e3bbde88d23cdea2693f780005b3909719ca",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "9dc763eb19d6d0e80072871cf081f106ee0fb9dd"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-while-statement-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Deleted the 'b' while statement",
|
||||
"Added the 'b' while statement",
|
||||
"Deleted the 'a' while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "9dc763eb19d6d0e80072871cf081f106ee0fb9dd",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "ed428faf84c293291bfbc4aac902639d7574ca38"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-while-statement-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Deleted the 'a' while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "ed428faf84c293291bfbc4aac902639d7574ca38",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "49240f42aaac1c78fb6c21b6f3dadc8c38ea130d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "javascript-while-statement-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"while-statement.js": [
|
||||
"Deleted the 'b' while statement"
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"while-statement.js"
|
||||
],
|
||||
"sha1": "49240f42aaac1c78fb6c21b6f3dadc8c38ea130d",
|
||||
"gitDir": "test/corpus/repos/javascript",
|
||||
"sha2": "150d2c57e7375a0937ec2d1f84faed6f49b55c84"
|
||||
}]
|
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"
|
||||
}]
|
408
test/corpus/generated/javascript.json
Normal file
408
test/corpus/generated/javascript.json
Normal file
@ -0,0 +1,408 @@
|
||||
[
|
||||
{
|
||||
"repoPath": "tools/semantic-git-diff/test/corpus/repos/javascript",
|
||||
"repoUrl": "https://github.com/rewinfrey/javascript.git",
|
||||
"language": "javascript",
|
||||
"syntaxes": [
|
||||
{
|
||||
"syntax": "object",
|
||||
"repoFilePath": "object.js",
|
||||
"insert": "{ \"key1\": \"value1\" };",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/string.json"
|
||||
},
|
||||
{
|
||||
"syntax": "number",
|
||||
"repoFilePath": "number.js",
|
||||
"insert": "101",
|
||||
"replacement": "102",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/number.json"
|
||||
},
|
||||
{
|
||||
"syntax": "variable",
|
||||
"repoFilePath": "variable.js",
|
||||
"insert": "theVar;",
|
||||
"replacement": "theVar2",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/variable.json"
|
||||
},
|
||||
{
|
||||
"syntax": "identifier",
|
||||
"repoFilePath": "identifier.js",
|
||||
"insert": "theVar;",
|
||||
"replacement": "theVar2",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/identifier.json"
|
||||
},
|
||||
{
|
||||
"syntax": "this-expression",
|
||||
"repoFilePath": "this-expression.js",
|
||||
"insert": "this;",
|
||||
"replacement": "return this;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/this-expression.json"
|
||||
},
|
||||
{
|
||||
"syntax": "null",
|
||||
"repoFilePath": "null.js",
|
||||
"insert": "null;",
|
||||
"replacement": "return null;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/null.json"
|
||||
},
|
||||
{
|
||||
"syntax": "undefined",
|
||||
"repoFilePath": "undefined.js",
|
||||
"insert": "undefined;",
|
||||
"replacement": "return undefined;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/undefined.json"
|
||||
},
|
||||
{
|
||||
"syntax": "true",
|
||||
"repoFilePath": "true.js",
|
||||
"insert": "true;",
|
||||
"replacement": "return true;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/true.json"
|
||||
},
|
||||
{
|
||||
"syntax": "false",
|
||||
"repoFilePath": "false.js",
|
||||
"insert": "false;",
|
||||
"replacement": "return false;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/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": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/class.json"
|
||||
},
|
||||
{
|
||||
"syntax": "array",
|
||||
"repoFilePath": "array.js",
|
||||
"insert": "[ \"item1\" ];",
|
||||
"replacement": "[ \"item1\", \"item2\" ];",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/array.json"
|
||||
},
|
||||
{
|
||||
"syntax": "function",
|
||||
"repoFilePath": "function.js",
|
||||
"insert": "function(arg1, arg2) { arg2; };",
|
||||
"replacement": "function(arg1, arg2) { arg1; };",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/named-function.json"
|
||||
},
|
||||
{
|
||||
"syntax": "member-access",
|
||||
"repoFilePath": "member-access.js",
|
||||
"insert": "x.someProperty;",
|
||||
"replacement": "x.someOtherProperty",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/member-access.json"
|
||||
},
|
||||
{
|
||||
"syntax": "subscript-access-variable",
|
||||
"repoFilePath": "subscript-access-variable.js",
|
||||
"insert": "x[someVariable];",
|
||||
"replacement": "x[someOtherVariable];",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/chained-callbacks.json"
|
||||
},
|
||||
{
|
||||
"syntax": "function-call",
|
||||
"repoFilePath": "function-call.js",
|
||||
"insert": "someFunction(arg1, \"arg2\");",
|
||||
"replacement": "someFunction(arg1, \"arg3\");",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/math-operator.json"
|
||||
},
|
||||
{
|
||||
"syntax": "boolean-operator",
|
||||
"repoFilePath": "boolean-operator.js",
|
||||
"insert": "i || j;",
|
||||
"replacement": "i && j;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/boolean-operator.json"
|
||||
},
|
||||
{
|
||||
"syntax": "bitwise-operator",
|
||||
"repoFilePath": "bitwise-operator.js",
|
||||
"insert": "i >> j;",
|
||||
"replacement": "i >> k;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/bitwise-operator.json"
|
||||
},
|
||||
{
|
||||
"syntax": "relational-operator",
|
||||
"repoFilePath": "relational-operator.js",
|
||||
"insert": "x < y;",
|
||||
"replacement": "x <= y;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/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": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/for-statement.json"
|
||||
},
|
||||
{
|
||||
"syntax": "assignment",
|
||||
"repoFilePath": "assignment.js",
|
||||
"insert": "x = 0;",
|
||||
"replacement": "x = 1;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/ternary.json"
|
||||
},
|
||||
{
|
||||
"syntax": "type-operator",
|
||||
"repoFilePath": "type-operator.js",
|
||||
"insert": "typeof x;",
|
||||
"replacement": "x instanceof String;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/type-operator.json"
|
||||
},
|
||||
{
|
||||
"syntax": "delete-operator",
|
||||
"repoFilePath": "delete-operator.js",
|
||||
"insert": "delete thing['prop'];",
|
||||
"replacement": "delete thing.prop",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/delete-operator.json"
|
||||
},
|
||||
{
|
||||
"syntax": "void-operator",
|
||||
"repoFilePath": "void-operator.js",
|
||||
"insert": "void b()",
|
||||
"replacement": "void c()",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/void-operator.json"
|
||||
},
|
||||
{
|
||||
"syntax": "math-assignment-operator",
|
||||
"repoFilePath": "math-assignment-operator.js",
|
||||
"insert": "x += 1;",
|
||||
"replacement": "x += 2;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/do-while-statement.json"
|
||||
},
|
||||
{
|
||||
"syntax": "return-statement",
|
||||
"repoFilePath": "return-statement.js",
|
||||
"insert": "return 5;",
|
||||
"replacement": "return;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/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": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/try-statement.json"
|
||||
},
|
||||
{
|
||||
"syntax": "regex",
|
||||
"repoFilePath": "regex.js",
|
||||
"insert": "/one/g;",
|
||||
"replacement": "/on[^/]afe/gim;",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/regex.json"
|
||||
},
|
||||
{
|
||||
"syntax": "if",
|
||||
"repoFilePath": "if.js",
|
||||
"insert": "if (x) { log(y); }",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/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": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/if-else.json"
|
||||
},
|
||||
{
|
||||
"syntax": "template-string",
|
||||
"repoFilePath": "template-string.js",
|
||||
"insert": "`one line`",
|
||||
"replacement": "`multi line`",
|
||||
"testCaseFilePath": "tools/semantic-git-diff/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": "tools/semantic-git-diff/test/corpus/diff-summaries/javascript/for-in-statement.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 12621d999238618e3a862f232779862ba803a778
|
Loading…
Reference in New Issue
Block a user