1
1
mirror of https://github.com/github/semantic.git synced 2024-11-28 18:23:44 +03:00

Merge pull request #863 from github/add-source-spans

Add source spans to diff summaries
This commit is contained in:
Timothy Clem 2016-10-11 14:34:47 -07:00 committed by GitHub
commit f40f995e56
82 changed files with 17026 additions and 2162 deletions

View File

@ -133,7 +133,7 @@ runCommitAndTestCaseGeneration :: GeneratorArgs -> String -> FilePath -> JSONMet
runCommitAndTestCaseGeneration opts language repoPath metaSyntax@JSONMetaSyntax{..} =
traverse_ (runGenerateCommitAndTestCase opts language repoPath) (commands metaSyntax)
maybeMapSummary :: [R.Output] -> [Maybe (Map Text (Map Text [Text]))]
maybeMapSummary :: [R.Output] -> [Maybe (Map Text (Map Text [Value]))]
maybeMapSummary = fmap $ \case
R.SummaryOutput output -> Just output
_ -> Nothing
@ -172,7 +172,7 @@ runGenerateCommitAndTestCase opts language repoPath (JSONMetaSyntax{..}, descrip
-- | 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 :: String -> String -> FilePath -> FilePath -> GeneratorArgs -> IO (Maybe (Map Text [Value]), Maybe (Map Text [Value]))
runMaybeSummaries beforeSha afterSha repoPath repoFilePath GeneratorArgs{..}
| generateResults = do
diffs <- fetchDiffs $ args repoPath beforeSha afterSha [repoFilePath] R.Summary

View File

@ -1,6 +1,6 @@
{-# LANGUAGE DataKinds, TypeFamilies, ScopedTypeVariables #-}
{-# LANGUAGE DataKinds, TypeFamilies, ScopedTypeVariables, DeriveAnyClass #-}
module DiffSummary (diffSummaries, DiffSummary(..), DiffInfo(..), diffToDiffSummaries, isBranchInfo) where
module DiffSummary (diffSummaries, DiffSummary(..), DiffInfo(..), diffToDiffSummaries, isBranchInfo, isErrorSummary, JSONSummary(..)) where
import Prologue hiding (intercalate)
import Diff
@ -21,6 +21,7 @@ import Text.PrettyPrint.Leijen.Text ((<+>), squotes, space, string, Doc, punctua
import qualified Text.PrettyPrint.Leijen.Text as P
import SourceSpan
import Source
import Data.Aeson as A
data Annotatable a = Annotatable a | Unannotatable a
@ -53,7 +54,19 @@ identifiable term = isIdentifiable (unwrap term) term
S.Export{} -> Identifiable
_ -> Unidentifiable
data DiffInfo = LeafInfo { categoryName :: Text, termName :: Text }
data JSONSummary summary span = JSONSummary { summary :: summary, span :: span }
| ErrorSummary { summary :: summary, span :: span }
deriving (Generic, Eq, Show)
instance (ToJSON summary, ToJSON span) => ToJSON (JSONSummary summary span) where
toJSON JSONSummary{..} = object [ "summary" .= summary, "span" .= span ]
toJSON ErrorSummary{..} = object [ "summary" .= summary, "span" .= span ]
isErrorSummary :: JSONSummary summary span -> Bool
isErrorSummary ErrorSummary{} = True
isErrorSummary _ = False
data DiffInfo = LeafInfo { categoryName :: Text, termName :: Text, sourceSpan :: SourceSpan }
| BranchInfo { branches :: [ DiffInfo ], categoryName :: Text, branchType :: Branch }
| ErrorInfo { errorSpan :: SourceSpan, termName :: Text }
deriving (Eq, Show)
@ -66,16 +79,20 @@ data DiffSummary a = DiffSummary {
} deriving (Eq, Functor, Show, Generic)
-- Returns a list of diff summary texts given two source blobs and a diff.
diffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range) => Both SourceBlob -> SyntaxDiff leaf fields -> [Either Text Text]
diffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range, HasField fields SourceSpan) =>
Both SourceBlob ->
SyntaxDiff leaf fields ->
[JSONSummary Text SourceSpans]
diffSummaries blobs diff = summaryToTexts =<< diffToDiffSummaries (source <$> blobs) diff
-- Takes a 'DiffSummary' and returns a list of summary texts representing the LeafInfos
-- in that 'DiffSummary'.
summaryToTexts :: DiffSummary DiffInfo -> [Either Text Text]
summaryToTexts DiffSummary{..} = runJoin . fmap (show . (<+> parentContexts parentAnnotation)) <$> (Join <$> summaries patch)
summaryToTexts :: DiffSummary DiffInfo -> [JSONSummary Text SourceSpans]
summaryToTexts DiffSummary{..} = (\jsonSummary ->
jsonSummary { summary = show $ summary jsonSummary <+> parentContexts parentAnnotation }) <$> summaries patch
-- Returns a list of 'DiffSummary' given two source blobs and a diff.
diffToDiffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range) => Both (Source Char) -> SyntaxDiff leaf fields -> [DiffSummary DiffInfo]
diffToDiffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Both (Source Char) -> SyntaxDiff leaf fields -> [DiffSummary DiffInfo]
diffToDiffSummaries sources = para $ \diff ->
let
diff' = free (Prologue.fst <$> diff)
@ -91,24 +108,27 @@ diffToDiffSummaries sources = para $ \diff ->
where
(beforeSource, afterSource) = runJoin sources
-- Returns a list of diff summary 'Docs' prefixed given a 'Patch'.
summaries :: Patch DiffInfo -> [Either Doc Doc]
summaries patch = eitherErrorOrDoc <$> patchToDoc patch
where eitherErrorOrDoc = if any hasErrorInfo patch then Left else Right
-- Flattens a patch of diff infos into a list of docs, one for every 'LeafInfo'
-- or `ErrorInfo` it contains.
patchToDoc :: Patch DiffInfo -> [Doc]
patchToDoc = \case
p@(Replace i1 i2) -> zipWith (\a b -> prefixWithPatch p a <+> "with" <+> determiner i1 <+> b) (toLeafInfos i1) (toLeafInfos i2)
p@(Insert info) -> prefixWithPatch p <$> toLeafInfos info
p@(Delete info) -> prefixWithPatch p <$> toLeafInfos info
-- Flattens a patch of diff infos into a list of docs, one for every 'LeafInfo' or `ErrorInfo` it contains.
summaries :: Patch DiffInfo -> [JSONSummary Doc SourceSpans]
summaries = \case
p@(Replace i1 i2) -> zipWith (\a b ->
JSONSummary
{
summary = summary (prefixWithPatch p This a) <+> "with" <+> determiner i1 <+> summary b
, span = SourceSpans $ These (span a) (span b)
}) (toLeafInfos i1) (toLeafInfos i2)
p@(Insert info) -> prefixWithPatch p That <$> toLeafInfos info
p@(Delete info) -> prefixWithPatch p This <$> toLeafInfos info
-- Prefixes a given doc with the type of patch it represents.
prefixWithPatch :: Patch DiffInfo -> Doc -> Doc
prefixWithPatch patch = prefixWithThe (patchToPrefix patch)
prefixWithPatch :: Patch DiffInfo -> (SourceSpan -> These SourceSpan SourceSpan) -> JSONSummary Doc SourceSpan -> JSONSummary Doc SourceSpans
prefixWithPatch patch constructor = prefixWithThe (patchToPrefix patch)
where
prefixWithThe prefix doc = prefix <+> determiner' patch <+> doc
prefixWithThe prefix jsonSummary = jsonSummary
{
summary = prefix <+> determiner' patch <+> summary jsonSummary
, span = SourceSpans $ constructor (span jsonSummary)
}
patchToPrefix = \case
(Replace _ _) -> "Replaced"
(Insert _) -> "Added"
@ -117,21 +137,23 @@ prefixWithPatch patch = prefixWithThe (patchToPrefix patch)
-- Optional determiner (e.g. "the") to tie together summary statements.
determiner :: DiffInfo -> Doc
determiner (LeafInfo "number" _) = ""
determiner (LeafInfo "boolean" _) = ""
determiner (LeafInfo "anonymous function" _) = "an"
determiner (LeafInfo "number" _ _) = ""
determiner (LeafInfo "boolean" _ _) = ""
determiner (LeafInfo "anonymous function" _ _) = "an"
determiner (BranchInfo bs _ _) = determiner (last bs)
determiner _ = "the"
toLeafInfos :: DiffInfo -> [Doc]
toLeafInfos (LeafInfo "number" termName) = pure (squotes (toDoc termName))
toLeafInfos (LeafInfo "boolean" termName) = pure (squotes (toDoc termName))
toLeafInfos (LeafInfo "anonymous function" termName) = pure (toDoc termName)
toLeafInfos (LeafInfo cName@"string" termName) = pure (toDoc termName <+> toDoc cName)
toLeafInfos (LeafInfo cName@"export statement" termName) = pure (toDoc termName <+> toDoc cName)
toLeafInfos LeafInfo{..} = pure (squotes (toDoc termName) <+> toDoc categoryName)
toLeafInfos BranchInfo{..} = toLeafInfos =<< branches
toLeafInfos err@ErrorInfo{} = pure (pretty err)
toLeafInfos :: DiffInfo -> [JSONSummary Doc SourceSpan]
toLeafInfos err@ErrorInfo{..} = pure $ ErrorSummary (pretty err) errorSpan
toLeafInfos BranchInfo{..} = branches >>= toLeafInfos
toLeafInfos leaf = pure . flip JSONSummary (sourceSpan leaf) $ case leaf of
(LeafInfo "number" termName _) -> squotes $ toDoc termName
(LeafInfo "boolean" termName _) -> squotes $ toDoc termName
(LeafInfo "anonymous function" termName _) -> toDoc termName
(LeafInfo cName@"string" termName _) -> toDoc termName <+> toDoc cName
(LeafInfo cName@"export statement" termName _) -> toDoc termName <+> toDoc cName
LeafInfo{..} -> squotes (toDoc termName) <+> toDoc categoryName
node -> panic $ "Expected a leaf info but got a: " <> show node
-- Returns a text representing a specific term given a source and a term.
toTermName :: forall leaf fields. (HasCategory leaf, HasField fields Category, HasField fields Range) => Source Char -> SyntaxTerm leaf fields -> Text
@ -172,7 +194,7 @@ toTermName source term = case unwrap term of
S.Object kvs -> "{ " <> intercalate ", " (toTermName' <$> kvs) <> " }"
S.Pair a _ -> toTermName' a <> ": …"
S.Return expr -> maybe "empty" toTermName' expr
S.Error _ _ -> termNameFromSource term
S.Error _ -> termNameFromSource term
S.If expr _ _ -> termNameFromSource expr
S.For clauses _ -> termNameFromChildren term clauses
S.While expr _ -> toTermName' expr
@ -214,14 +236,14 @@ parentContexts contexts = hsep $ either identifiableDoc annotatableDoc <$> conte
toDoc :: Text -> Doc
toDoc = string . toS
termToDiffInfo :: (HasCategory leaf, HasField fields Category, HasField fields Range) => Source Char -> SyntaxTerm leaf fields -> DiffInfo
termToDiffInfo :: (HasCategory leaf, HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Source Char -> SyntaxTerm leaf fields -> DiffInfo
termToDiffInfo blob term = case unwrap term of
S.Indexed children -> BranchInfo (termToDiffInfo' <$> children) (toCategoryName term) BIndexed
S.Fixed children -> BranchInfo (termToDiffInfo' <$> children) (toCategoryName term) BFixed
S.AnonymousFunction _ _ -> LeafInfo "anonymous function" (toTermName' term)
S.AnonymousFunction _ _ -> LeafInfo "anonymous function" (toTermName' term) (getField $ extract term)
Commented cs leaf -> BranchInfo (termToDiffInfo' <$> cs <> maybeToList leaf) (toCategoryName term) BCommented
S.Error sourceSpan _ -> ErrorInfo sourceSpan (toTermName' term)
_ -> LeafInfo (toCategoryName term) (toTermName' term)
S.Error _ -> ErrorInfo (getField $ extract term) (toTermName' term)
_ -> LeafInfo (toCategoryName term) (toTermName' term) (getField $ extract term)
where toTermName' = toTermName blob
termToDiffInfo' = termToDiffInfo blob
@ -244,12 +266,6 @@ isBranchInfo info = case info of
BranchInfo{} -> True
_ -> False
hasErrorInfo :: DiffInfo -> Bool
hasErrorInfo info = case info of
(ErrorInfo _ _) -> True
(BranchInfo branches _ _) -> any hasErrorInfo branches
_ -> False
-- The user-facing category name of 'a'.
class HasCategory a where
toCategoryName :: a -> Text
@ -329,4 +345,4 @@ instance Arbitrary a => Arbitrary (DiffSummary a) where
instance P.Pretty DiffInfo where
pretty LeafInfo{..} = squotes (string $ toSL termName) <+> string (toSL categoryName)
pretty BranchInfo{..} = mconcat $ punctuate (string "," P.<> space) (pretty <$> branches)
pretty ErrorInfo{..} = squotes (string $ toSL termName) <+> "at" <+> (string . toSL $ displayStartEndPos errorSpan) <+> "in" <+> (string . toSL $ spanName errorSpan)
pretty ErrorInfo{..} = squotes (string $ toSL termName) <+> "at" <+> (string . toSL $ displayStartEndPos errorSpan)

View File

@ -68,7 +68,7 @@ diffFiles parser renderer sourceBlobs = do
_ -> Nothing)
-- | Return a parser based on the file extension (including the ".").
parserForType :: Text -> Parser (Syntax Text) (Record '[Range, Category])
parserForType :: Text -> Parser (Syntax Text) (Record '[Range, Category, SourceSpan])
parserForType mediaType = case languageForType mediaType of
Just C -> treeSitterParser C ts_language_c
Just JavaScript -> treeSitterParser JavaScript ts_language_javascript
@ -77,20 +77,19 @@ parserForType mediaType = case languageForType mediaType of
_ -> lineByLineParser
-- | A fallback parser that treats a file simply as rows of strings.
lineByLineParser :: Parser (Syntax Text) (Record '[Range, Category])
lineByLineParser blob = pure . cofree . root $ case foldl' annotateLeaves ([], 0) lines of
lineByLineParser :: Parser (Syntax Text) (Record '[Range, Category, SourceSpan])
lineByLineParser SourceBlob{..} = pure . cofree . root $ case foldl' annotateLeaves ([], 0) lines of
(leaves, _) -> cofree <$> leaves
where
input = source blob
lines = actualLines input
root children = (Range 0 (length input) .: Program .: RNil) :< Indexed children
leaf charIndex line = (Range charIndex (charIndex + T.length line) .: Program .: RNil) :< Leaf line
lines = actualLines source
root children = (Range 0 (length source) .: Program .: rangeToSourceSpan source (Range 0 (length source)) .: RNil) :< Indexed children
leaf charIndex line = (Range charIndex (charIndex + T.length line) .: Program .: rangeToSourceSpan source (Range charIndex (charIndex + T.length line)) .: RNil) :< Leaf line
annotateLeaves (accum, charIndex) line =
(accum <> [ leaf charIndex (toText line) ] , charIndex + length line)
toText = T.pack . Source.toString
-- | Return the parser that should be used for a given path.
parserForFilepath :: FilePath -> Parser (Syntax Text) (Record '[Cost, Range, Category])
parserForFilepath :: FilePath -> Parser (Syntax Text) (Record '[Cost, Range, Category, SourceSpan])
parserForFilepath path blob = decorateTerm termCostDecorator <$> parserForType (toS (takeExtension path)) blob
-- | Transcode a file to a unicode source.
@ -128,7 +127,7 @@ diffCostWithCachedTermCosts diff = unCost $ case runFree diff of
Pure patch -> sum (cost . extract <$> patch)
-- | Returns a rendered diff given a parser, diff arguments and two source blobs.
textDiff :: (HasField fields Category, HasField fields Cost, HasField fields Range) => Parser (Syntax Text) (Record fields) -> DiffArguments -> Both SourceBlob -> IO Output
textDiff :: (HasField fields SourceSpan, HasField fields Category, HasField fields Cost, HasField fields Range) => Parser (Syntax Text) (Record fields) -> DiffArguments -> Both SourceBlob -> IO Output
textDiff parser arguments = diffFiles parser $ case format arguments of
Split -> split
Patch -> patch
@ -144,7 +143,7 @@ truncatedDiff arguments sources = pure $ case format arguments of
Summary -> SummaryOutput mempty
-- | Prints a rendered diff to stdio or a filepath given a parser, diff arguments and two source blobs.
printDiff :: (HasField fields Category, HasField fields Cost, HasField fields Range) => Parser (Syntax Text) (Record fields) -> DiffArguments -> Both SourceBlob -> IO ()
printDiff :: (HasField fields SourceSpan, HasField fields Category, HasField fields Cost, HasField fields Range) => Parser (Syntax Text) (Record fields) -> DiffArguments -> Both SourceBlob -> IO ()
printDiff parser arguments sources = do
rendered <- textDiff parser arguments sources
let renderedText = case rendered of

View File

@ -1,10 +1,11 @@
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving #-}
module Info (Range(..), characterRange, setCharacterRange, Category(..), category, setCategory, Cost(..), cost, setCost) where
module Info (Range(..), characterRange, setCharacterRange, Category(..), category, setCategory, Cost(..), cost, setCost, SourceSpan(..), SourcePos(..), SourceSpans(..)) where
import Data.Record
import Prologue
import Category
import Range
import SourceSpan
import Test.QuickCheck
newtype Cost = Cost { unCost :: Int }

View File

@ -5,7 +5,6 @@ import Data.Record
import Info
import Prologue
import Source
import SourceSpan
import qualified Syntax as S
import Term
@ -45,11 +44,14 @@ termConstructor
-> IO SourceSpan -- ^ The span that the term occupies. This is passed in 'IO' to guarantee some access constraints & encourage its use only when needed (improving performance).
-> Text -- ^ The name of the production for this node.
-> Range -- ^ The character range that the term occupies.
-> [Term (S.Syntax Text) (Record '[Range, Category])] -- ^ The child nodes of the term.
-> IO (Term (S.Syntax Text) (Record '[Range, Category])) -- ^ The resulting term, in IO.
-> [Term (S.Syntax Text) (Record '[Range, Category, SourceSpan])] -- ^ The child nodes of the term.
-> IO (Term (S.Syntax Text) (Record '[Range, Category, SourceSpan])) -- ^ The resulting term, in IO.
termConstructor source sourceSpan name range children =
withDefaultInfo <$> case (name, children) of
("ERROR", _) -> S.Error <$> sourceSpan <*> pure children
(_, []) -> S.Leaf <$> pure (toText $ slice range source)
_ -> S.Indexed <$> pure children
where withDefaultInfo syntax = cofree ((range .: Other name .: RNil) :< syntax)
withDefaultInfo $ case (name, children) of
("ERROR", _) -> S.Error children
(_, []) -> S.Leaf (toText $ slice range source)
_ -> S.Indexed children
where
withDefaultInfo syntax = do
sourceSpan' <- sourceSpan
pure $! cofree ((range .: Other name .: sourceSpan' .: RNil) :< syntax)

View File

@ -5,7 +5,6 @@ import Data.Record
import Info
import Prologue
import Source
import SourceSpan
import Syntax
import qualified Syntax as S
import Term
@ -15,15 +14,17 @@ termConstructor
-> IO SourceSpan -- ^ The span that the term occupies. This is passed in 'IO' to guarantee some access constraints & encourage its use only when needed (improving performance).
-> Text -- ^ The name of the production for this node.
-> Range -- ^ The character range that the term occupies.
-> [Term (Syntax Text) (Record '[Range, Category])] -- ^ The child nodes of the term.
-> IO (Term (Syntax Text) (Record '[Range, Category])) -- ^ The resulting term, in IO.
-> [Term (Syntax Text) (Record '[Range, Category, SourceSpan])] -- ^ The child nodes of the term.
-> IO (Term (Syntax Text) (Record '[Range, Category, SourceSpan])) -- ^ The resulting term, in IO.
termConstructor source sourceSpan name range children
| name == "ERROR" = sourceSpan >>= withDefaultInfo . (`S.Error` children)
| name == "ERROR" = withDefaultInfo (S.Error children)
| otherwise = withDefaultInfo $ case (name, children) of
(_, []) -> S.Leaf . toText $ slice range source
_ -> S.Indexed children
where withDefaultInfo syntax = pure $! cofree ((range .: categoryForCProductionName name .: RNil) :< syntax)
where
withDefaultInfo syntax = do
sourceSpan' <- sourceSpan
pure $! cofree ((range .: categoryForCProductionName name .: sourceSpan' .: RNil) :< syntax)
categoryForCProductionName :: Text -> Category
categoryForCProductionName name = case name of
_ -> Other name
categoryForCProductionName name = Other name

View File

@ -5,7 +5,6 @@ import Data.Record
import Info
import Prologue
import Source
import SourceSpan
import qualified Syntax as S
import Term
@ -23,10 +22,10 @@ termConstructor
-> IO SourceSpan -- ^ The span that the term occupies. This is passed in 'IO' to guarantee some access constraints & encourage its use only when needed (improving performance).
-> Text -- ^ The name of the production for this node.
-> Range -- ^ The character range that the term occupies.
-> [Term (S.Syntax Text) (Record '[Range, Category])] -- ^ The child nodes of the term.
-> IO (Term (S.Syntax Text) (Record '[Range, Category])) -- ^ The resulting term, in IO.
-> [Term (S.Syntax Text) (Record '[Range, Category, SourceSpan])] -- ^ The child nodes of the term.
-> IO (Term (S.Syntax Text) (Record '[Range, Category, SourceSpan])) -- ^ The resulting term, in IO.
termConstructor source sourceSpan name range children
| name == "ERROR" = sourceSpan >>= withDefaultInfo . (`S.Error` children)
| name == "ERROR" = withDefaultInfo (S.Error children)
| otherwise = withDefaultInfo $ case (name, children) of
("return_statement", _) -> S.Return (listToMaybe children)
("assignment", [ identifier, value ]) -> S.Assignment identifier value
@ -37,16 +36,16 @@ termConstructor source sourceSpan name range children
S.Indexed rest -> S.Indexed $ a : rest
_ -> S.Indexed children
("function_call", _) -> case runCofree <$> children of
[ (_ :< S.MemberAccess{..}), (_ :< S.Args args) ] -> S.MethodCall memberId property args
[ (_ :< S.MemberAccess{..}) ] -> S.MethodCall memberId property []
[ function, (_ :< S.Args args) ] -> S.FunctionCall (cofree function) args
[ _ :< S.MemberAccess{..}, _ :< S.Args args ] -> S.MethodCall memberId property args
[ _ :< S.MemberAccess{..} ] -> S.MethodCall memberId property []
[ function, _ :< S.Args args ] -> S.FunctionCall (cofree function) args
(x:xs) -> S.FunctionCall (cofree x) (cofree <$> xs)
_ -> S.Indexed children
("ternary", (condition:cases)) -> S.Ternary condition cases
("ternary", condition : cases) -> S.Ternary condition cases
("arguments", _) -> S.Args children
("var_assignment", [ x, y ]) -> S.VarAssignment x y
("var_declaration", _) -> S.Indexed $ toVarDecl <$> children
("switch_statement", (expr:rest)) -> S.Switch expr rest
("switch_statement", expr : rest) -> S.Switch expr rest
("case", [ expr, body ]) -> S.Case expr body
("object", _) -> S.Object $ foldMap toTuple children
("pair", _) -> S.Fixed children
@ -82,8 +81,12 @@ termConstructor source sourceSpan name range children
_ -> S.Indexed children
(_, []) -> S.Leaf . toText $ slice range source
_ -> S.Indexed children
where withDefaultInfo syntax@(S.MethodCall _ _ _) = pure $! cofree ((range .: MethodCall .: RNil) :< syntax)
withDefaultInfo syntax = pure $! cofree ((range .: categoryForJavaScriptProductionName name .: RNil) :< syntax)
where
withDefaultInfo syntax = do
sourceSpan' <- sourceSpan
pure $! case syntax of
S.MethodCall{} -> cofree ((range .: MethodCall .: sourceSpan' .: RNil) :< syntax)
_ -> cofree ((range .: categoryForJavaScriptProductionName name .: sourceSpan' .: RNil) :< syntax)
categoryForJavaScriptProductionName :: Text -> Category
categoryForJavaScriptProductionName name = case name of
@ -151,7 +154,7 @@ categoryForJavaScriptProductionName name = case name of
_ -> Other name
toVarDecl :: (HasField fields Category) => Term (S.Syntax Text) (Record fields) -> Term (S.Syntax Text) (Record fields)
toVarDecl child = cofree $ (setCategory (extract child) VarDecl :< S.VarDecl child)
toVarDecl child = cofree $ setCategory (extract child) VarDecl :< S.VarDecl child
toTuple :: Term (S.Syntax Text) (Record fields) -> [Term (S.Syntax Text) (Record fields)]
toTuple child | S.Indexed [key,value] <- unwrap child = [cofree (extract child :< S.Pair key value)]

View File

@ -9,19 +9,23 @@ import Parser
import Prologue
import Range
import Source
import SourceSpan
import Syntax
cmarkParser :: Parser (Syntax Text) (Record '[Range, Category])
cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source)
where toTerm :: Range -> Node -> Cofree (Syntax Text) (Record '[Range, Category])
toTerm within (Node position t children) = let range = maybe within (sourceSpanToRange source . toSpan) position in cofree $ (range .: toCategory t .: RNil) :< case t of
cmarkParser :: Parser (Syntax Text) (Record '[Range, Category, SourceSpan])
cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) (rangeToSourceSpan source $ totalRange source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source)
where toTerm :: Range -> SourceSpan -> Node -> Cofree (Syntax Text) (Record '[Range, Category, SourceSpan])
toTerm within withinSpan (Node position t children) =
let
range = maybe within (sourceSpanToRange source . toSpan) position
span = maybe withinSpan toSpan position
in
cofree $ (range .: toCategory t .: span .: RNil) :< case t of
-- Leaves
CODE text -> Leaf text
TEXT text -> Leaf text
CODE_BLOCK _ text -> Leaf text
-- Branches
_ -> Indexed (toTerm range <$> children)
_ -> Indexed (toTerm range span <$> children)
toCategory :: NodeType -> Category
toCategory (TEXT _) = Other "text"
@ -29,10 +33,10 @@ cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) $ commonmarkToNod
toCategory (HTML_BLOCK _) = Other "html"
toCategory (HTML_INLINE _) = Other "html"
toCategory (HEADING _) = Other "heading"
toCategory (LIST (ListAttributes{..})) = Other $ case listType of
toCategory (LIST ListAttributes{..}) = Other $ case listType of
BULLET_LIST -> "unordered list"
ORDERED_LIST -> "ordered list"
toCategory (LINK{}) = Other "link"
toCategory (IMAGE{}) = Other "image"
toCategory LINK{} = Other "link"
toCategory IMAGE{} = Other "image"
toCategory t = Other (show t)
toSpan PosInfo{..} = SourceSpan "" (SourcePos (pred startLine) (pred startColumn)) (SourcePos (pred endLine) endColumn)
toSpan PosInfo{..} = SourceSpan (SourcePos (pred startLine) (pred startColumn)) (SourcePos (pred endLine) endColumn)

View File

@ -20,7 +20,7 @@ data DiffArguments = DiffArguments { format :: Format, output :: Maybe FilePath
data Format = Split | Patch | JSON | Summary
deriving (Show)
data Output = SplitOutput Text | PatchOutput Text | JSONOutput (Map Text Value) | SummaryOutput (Map Text (Map Text [Text]))
data Output = SplitOutput Text | PatchOutput Text | JSONOutput (Map Text Value) | SummaryOutput (Map Text (Map Text [Value]))
deriving (Show)
-- Returns a key representing the filename. If the filenames are different,
@ -47,7 +47,7 @@ concatOutputs list | isJSON list = toS . encodingToLazyByteString . toEncoding $
concatJSON _ = mempty
concatOutputs list | isSummary list = toS . encodingToLazyByteString . toEncoding $ concatSummaries list
where
concatSummaries :: [Output] -> Map Text (Map Text [Text])
concatSummaries :: [Output] -> Map Text (Map Text [Value])
concatSummaries (SummaryOutput hash : rest) = Map.unionWith (Map.unionWith (<>)) hash (concatSummaries rest)
concatSummaries _ = mempty
concatOutputs list | isText list = T.intercalate "\n" (toText <$> list)

View File

@ -94,7 +94,7 @@ termFields info syntax = "range" .= characterRange info : "category" .= category
S.Constructor expr -> [ "constructorExpression" .= expr ]
S.Comment _ -> []
S.Commented comments child -> childrenFields (comments <> maybeToList child)
S.Error sourceSpan c -> [ "sourceSpan" .= sourceSpan ] <> childrenFields c
S.Error c -> childrenFields c
S.Throw c -> [ "throwExpression" .= c ]
S.Try body catch finally -> [ "tryBody" .= body ] <> [ "tryCatch" .= catch ] <> [ "tryFinally" .= finally ]
S.Array c -> childrenFields c

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TupleSections, ScopedTypeVariables #-}
module Renderer.Summary where
import Category
@ -9,15 +9,18 @@ import Range
import DiffSummary
import Data.Map as Map hiding (null)
import Source
import SourceSpan
import Data.Aeson
import Data.List as List
summary :: (HasField fields Category, HasField fields Range) => Renderer (Record fields)
summary :: (HasField fields Category, HasField fields Range, HasField fields SourceSpan) => Renderer (Record fields)
summary blobs diff = SummaryOutput $ Map.fromList [
("changes", changes),
("errors", errors)
]
where
changes = if null changes' then mempty else Map.singleton summaryKey changes'
errors = if null errors' then mempty else Map.singleton summaryKey errors'
(errors', changes') = partitionEithers summaries
changes = if null changes' then mempty else Map.singleton summaryKey (toJSON <$> changes')
errors = if null errors' then mempty else Map.singleton summaryKey (toJSON <$> errors')
(errors', changes') = List.partition isErrorSummary summaries
summaryKey = toSummaryKey (path <$> blobs)
summaries = diffSummaries blobs diff

View File

@ -91,7 +91,7 @@ actualLineRanges :: Range -> Source Char -> [Range]
actualLineRanges range = drop 1 . scanl toRange (Range (start range) (start range)) . actualLines . slice range
where toRange previous string = Range (end previous) $ end previous + length string
-- | Compute the character range corresponding to a given SourceSpan within a Source.
-- | Compute the character range given a Source and a SourceSpan.
sourceSpanToRange :: Source Char -> SourceSpan -> Range
sourceSpanToRange source SourceSpan{..} = Range start end
where start = sumLengths leadingRanges + column spanStart
@ -99,6 +99,14 @@ sourceSpanToRange source SourceSpan{..} = Range start end
(leadingRanges, remainingRanges) = splitAt (line spanStart) (actualLineRanges (totalRange source) source)
sumLengths = sum . fmap (\ Range{..} -> end - start)
rangeToSourceSpan :: Source Char -> Range -> SourceSpan
rangeToSourceSpan source range@Range{} = SourceSpan startPos endPos
where startPos = maybe (SourcePos 1 1) (toStartPos 1) (head lineRanges)
endPos = toEndPos (length lineRanges) (last lineRanges)
lineRanges = actualLineRanges range source
toStartPos line range = SourcePos line (start range)
toEndPos line range = SourcePos line (end range)
instance Semigroup (Source a) where
Source a <> Source b = Source (a Vector.++ b)

View File

@ -9,6 +9,7 @@ import Prologue
import Data.Aeson ((.=), (.:))
import qualified Data.Aeson as A
import Test.QuickCheck
import Data.These
import Data.Text.Arbitrary()
-- |
@ -40,13 +41,9 @@ instance A.FromJSON SourcePos where
data SourceSpan = SourceSpan
{ -- |
-- Source name
--
spanName :: !Text
-- |
-- Start of the span
--
, spanStart :: !SourcePos
spanStart :: !SourcePos
-- End of the span
--
, spanEnd :: !SourcePos
@ -56,28 +53,36 @@ displayStartEndPos :: SourceSpan -> Text
displayStartEndPos sp =
displaySourcePos (spanStart sp) <> " - " <> displaySourcePos (spanEnd sp)
displaySourceSpan :: SourceSpan -> Text
displaySourceSpan sp =
spanName sp <> " " <> displayStartEndPos sp
instance A.ToJSON SourceSpan where
toJSON SourceSpan{..} =
A.object [ "name" .= spanName
, "start" .= spanStart
, "end" .= spanEnd
A.object [ "start" .= spanStart
, "end" .= spanEnd
]
instance A.FromJSON SourceSpan where
parseJSON = A.withObject "SourceSpan" $ \o ->
SourceSpan <$>
o .: "name" <*>
SourceSpan <$>
o .: "start" <*>
o .: "end"
newtype SourceSpans = SourceSpans { unSourceSpans :: These SourceSpan SourceSpan }
deriving (Eq, Show)
instance A.ToJSON SourceSpans where
toJSON (SourceSpans spans) = case spans of
(This span) -> A.object ["delete" .= span]
(That span) -> A.object ["insert" .= span]
(These span1 span2) -> A.object ["replace" .= (span1, span2)]
toEncoding (SourceSpans spans) = case spans of
(This span) -> A.pairs $ "delete" .= span
(That span) -> A.pairs $ "insert" .= span
(These span1 span2) -> A.pairs $ "replace" .= (span1, span2)
instance Arbitrary SourcePos where
arbitrary = SourcePos <$> arbitrary <*> arbitrary
shrink = genericShrink
instance Arbitrary SourceSpan where
arbitrary = SourceSpan <$> arbitrary <*> arbitrary <*> arbitrary
arbitrary = SourceSpan <$> arbitrary <*> arbitrary
shrink = genericShrink

View File

@ -5,7 +5,6 @@ import Prologue
import Data.Mergeable
import GHC.Generics
import Test.QuickCheck hiding (Fixed)
import SourceSpan
-- | A node in an abstract syntax tree.
--
@ -57,7 +56,7 @@ data Syntax a f
| Comment a
-- | A term preceded or followed by any number of comments.
| Commented [f] (Maybe f)
| Error SourceSpan [f]
| Error [f]
| For [f] f
| DoWhile { doWhileBody :: f, doWhileExpr :: f }
| While { whileExpr :: f, whileBody :: f }

View File

@ -19,7 +19,7 @@ import SourceSpan
import Info
-- | Returns a TreeSitter parser for the given language and TreeSitter grammar.
treeSitterParser :: Language -> Ptr TS.Language -> Parser (Syntax.Syntax Text) (Record '[Range, Category])
treeSitterParser :: Language -> Ptr TS.Language -> Parser (Syntax.Syntax Text) (Record '[Range, Category, SourceSpan])
treeSitterParser language grammar blob = do
document <- ts_document_new
ts_document_set_language document grammar
@ -31,7 +31,7 @@ treeSitterParser language grammar blob = do
pure term)
-- | Return a parser for a tree sitter language & document.
documentToTerm :: Language -> Ptr Document -> Parser (Syntax.Syntax Text) (Record '[Range, Category])
documentToTerm :: Language -> Ptr Document -> Parser (Syntax.Syntax Text) (Record '[Range, Category, SourceSpan])
documentToTerm language document SourceBlob{..} = alloca $ \ root -> do
ts_document_root_node_p document root
toTerm root
@ -43,9 +43,9 @@ documentToTerm language document SourceBlob{..} = alloca $ \ root -> do
let range = Range { start = fromIntegral $ ts_node_p_start_char node, end = fromIntegral $ ts_node_p_end_char node }
let sourceSpan = SourceSpan { spanName = toS path
, spanStart = SourcePos (fromIntegral $! ts_node_p_start_point_row node) (fromIntegral $! ts_node_p_start_point_column node)
, spanEnd = SourcePos (fromIntegral $! ts_node_p_end_point_row node) (fromIntegral $! ts_node_p_end_point_column node) }
let startPos = SourcePos (1 + (fromIntegral $! ts_node_p_start_point_row node)) (1 + (fromIntegral $! ts_node_p_start_point_column node))
let endPos = SourcePos (1 + (fromIntegral $! ts_node_p_end_point_row node)) (1 + (fromIntegral $! ts_node_p_end_point_column node))
let sourceSpan = SourceSpan { spanStart = startPos , spanEnd = endPos }
-- Note: The strict application here is semantically important.
-- Without it, we may not evaluate the range until after weve exited

View File

@ -75,7 +75,7 @@ normalizeName path = addExtension (dropExtension $ dropExtension path) (takeExte
-- | Given file paths for A, B, and, optionally, a diff, return whether diffing
-- | the files will produce the diff. If no diff is provided, then the result
-- | is true, but the diff will still be calculated.
testDiff :: Renderer (Record '[Vector.Vector Double, Cost, Range, Category]) -> Both (Maybe FilePath) -> Maybe FilePath -> (Maybe Verbatim -> Maybe Verbatim -> Expectation) -> Expectation
testDiff :: Renderer (Record '[Vector.Vector Double, Cost, Range, Category, SourceSpan]) -> Both (Maybe FilePath) -> Maybe FilePath -> (Maybe Verbatim -> Maybe Verbatim -> Expectation) -> Expectation
testDiff renderer paths diff matcher = do
sources <- traverse (traverse readAndTranscodeFile) paths
actual <- fmap Verbatim <$> traverse ((pure . concatOutputs . pure) <=< diffFiles' sources) parser

View File

@ -20,21 +20,25 @@ import Term.Arbitrary
import Test.Hspec (Spec, describe, it, parallel)
import Test.Hspec.Expectations.Pretty
import Test.Hspec.QuickCheck
import Data.These
arrayInfo :: Record '[Category, Range]
arrayInfo = ArrayLiteral .: Range 0 3 .: RNil
sourceSpanBetween :: (Int, Int) -> (Int, Int) -> SourceSpan
sourceSpanBetween (s1, e1) (s2, e2) = SourceSpan (SourcePos s1 e1) (SourcePos s2 e2)
literalInfo :: Record '[Category, Range]
literalInfo = StringLiteral .: Range 1 2 .: RNil
arrayInfo :: Record '[Category, Range, SourceSpan]
arrayInfo = ArrayLiteral .: Range 0 3 .: sourceSpanBetween (1, 1) (1, 5) .: RNil
testDiff :: Diff (Syntax Text) (Record '[Category, Range])
literalInfo :: Record '[Category, Range, SourceSpan]
literalInfo = StringLiteral .: Range 1 2 .: sourceSpanBetween (1, 2) (1, 4) .: RNil
testDiff :: Diff (Syntax Text) (Record '[Category, Range, SourceSpan])
testDiff = free $ Free (pure arrayInfo :< Indexed [ free $ Pure (Insert (cofree $ literalInfo :< Leaf "\"a\"")) ])
testSummary :: DiffSummary DiffInfo
testSummary = DiffSummary { patch = Insert (LeafInfo "string" "a"), parentAnnotation = [] }
testSummary = DiffSummary { patch = Insert (LeafInfo "string" "a" $ sourceSpanBetween (1,1) (1, 2)), parentAnnotation = [] }
replacementSummary :: DiffSummary DiffInfo
replacementSummary = DiffSummary { patch = Replace (LeafInfo "string" "a") (LeafInfo "symbol" "b"), parentAnnotation = [Left (Info.FunctionCall, "foo")] }
replacementSummary = DiffSummary { patch = Replace (LeafInfo "string" "a" $ sourceSpanBetween (1, 2) (1, 4)) (LeafInfo "symbol" "b" $ sourceSpanBetween (1,1) (1, 2)), parentAnnotation = [Left (Info.FunctionCall, "foo")] }
blobs :: Both SourceBlob
blobs = both (SourceBlob (fromText "[]") nullOid "a.js" (Just defaultPlainBlob)) (SourceBlob (fromText "[a]") nullOid "b.js" (Just defaultPlainBlob))
@ -43,16 +47,16 @@ spec :: Spec
spec = parallel $ do
describe "diffSummaries" $ do
it "outputs a diff summary" $ do
diffSummaries blobs testDiff `shouldBe` [ Right $ "Added the \"a\" string" ]
diffSummaries blobs testDiff `shouldBe` [ JSONSummary "Added the \"a\" string" (SourceSpans . That $ sourceSpanBetween (1, 2) (1, 4)) ]
prop "equal terms produce identity diffs" $
\ a -> let term = defaultFeatureVectorDecorator (category . headF) (toTerm (a :: ArbitraryTerm Text (Record '[Category, Range]))) in
\ a -> let term = defaultFeatureVectorDecorator (category . headF) (toTerm (a :: ArbitraryTerm Text (Record '[Category, Range, SourceSpan]))) in
diffSummaries blobs (diffTerms wrap (==) diffCost term term) `shouldBe` []
describe "DiffInfo" $ do
prop "patches in summaries match the patches in diffs" $
\a -> let
diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category, Cost, Range])))
diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category, Cost, Range, SourceSpan])))
summaries = diffToDiffSummaries (source <$> blobs) diff
patches = toList diff
in
@ -61,14 +65,14 @@ spec = parallel $ do
(() <$ branchPatches, () <$ otherPatches) `shouldBe` (() <$ branchDiffPatches, () <$ otherDiffPatches)
prop "generates one LeafInfo for each child in an arbitrary branch patch" $
\a -> let
diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category, Range])))
diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category, Range, SourceSpan])))
diffInfoPatches = patch <$> diffToDiffSummaries (source <$> blobs) diff
syntaxPatches = toList diff
extractLeaves :: DiffInfo -> [DiffInfo]
extractLeaves (BranchInfo children _ _) = join $ extractLeaves <$> children
extractLeaves leaf = [ leaf ]
extractDiffLeaves :: Term (Syntax Text) (Record '[Category, Range]) -> [ Term (Syntax Text) (Record '[Category, Range]) ]
extractDiffLeaves :: Term (Syntax Text) (Record '[Category, Range, SourceSpan]) -> [ Term (Syntax Text) (Record '[Category, Range, SourceSpan]) ]
extractDiffLeaves term = case unwrap term of
(Indexed children) -> join $ extractDiffLeaves <$> children
(Fixed children) -> join $ extractDiffLeaves <$> children

View File

@ -24,7 +24,7 @@ data JSONTestCase = JSONTestCase { gitDir :: !String
, filePaths :: ![String]
, sha1 :: !String
, sha2 :: !String
, expectedResult :: !(Map Text (Map Text [Text]))
, expectedResult :: !(Map Text (Map Text [Value]))
} deriving (Show, Generic, FromJSON)
instance ToJSON JSONTestCase where

View File

@ -20,14 +20,14 @@ 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 -> (Either String (Map Text (Map Text [Value])) -> Either String (Map Text (Map Text [Value])) -> Expectation) -> Expectation
assertDiffSummary JSONTestCase {..} format matcher = do
diffs <- fetchDiffs $ args gitDir sha1 sha2 filePaths format
result <- catchException . pure . pure . concatOutputs $ diffs
let actual = eitherDecode . DL.fromStrict . encodeUtf8 . fromJust $ listToMaybe result
matcher actual (Right expectedResult)
runTestsIn :: [FilePath] -> Format -> (Either String (Map Text (Map Text [Text])) -> Either String (Map Text (Map Text [Text])) -> Expectation) -> SpecWith ()
runTestsIn :: [FilePath] -> Format -> (Either String (Map Text (Map Text [Value])) -> Either String (Map Text (Map Text [Value])) -> Expectation) -> SpecWith ()
runTestsIn filePaths format matcher = do
contents <- runIO $ traverse DL.readFile filePaths
let filePathContents = zip filePaths contents

View File

@ -21,7 +21,7 @@ spec = parallel $ do
describe "sourceSpanToRange" $ do
prop "computes single-line ranges" $
\ s -> let source = fromList s
spans = zipWith (\ i Range {..} -> SourceSpan "" (SourcePos i 0) (SourcePos i (end - start))) [0..] ranges
spans = zipWith (\ i Range {..} -> SourceSpan (SourcePos i 0) (SourcePos i (end - start))) [0..] ranges
ranges = actualLineRanges (totalRange source) source in
sourceSpanToRange source <$> spans `shouldBe` ranges
@ -35,13 +35,13 @@ spec = parallel $ do
describe "totalSpan" $ do
prop "covers single lines" $
\ n -> totalSpan (fromList (replicate n '*')) `shouldBe` SourceSpan "" (SourcePos 0 0) (SourcePos 0 (max 0 n))
\ n -> totalSpan (fromList (replicate n '*')) `shouldBe` SourceSpan (SourcePos 0 0) (SourcePos 0 (max 0 n))
prop "covers multiple lines" $
\ n -> totalSpan (fromList (intersperse '\n' (replicate n '*'))) `shouldBe` SourceSpan "" (SourcePos 0 0) (SourcePos (max 0 (pred n)) (if n > 0 then 1 else 0))
\ n -> totalSpan (fromList (intersperse '\n' (replicate n '*'))) `shouldBe` SourceSpan (SourcePos 0 0) (SourcePos (max 0 (pred n)) (if n > 0 then 1 else 0))
totalSpan :: Source Char -> SourceSpan
totalSpan source = SourceSpan "" (SourcePos 0 0) (SourcePos (pred (length ranges)) (end lastRange - start lastRange))
totalSpan source = SourceSpan (SourcePos 0 0) (SourcePos (pred (length ranges)) (end lastRange - start lastRange))
where ranges = actualLineRanges (totalRange source) source
lastRange = Prelude.last ranges

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"anonymous-function.js": [
"Added an anonymous(a, b) function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Added an anonymous(a, b) function"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "9da531dab73d3a68d171641dcc1913ad7225de16",
"sha1": "4eda6b0a46046cb99a4544fe3a4a9c23e702eeac",
"gitDir": "test/corpus/repos/javascript",
"sha2": "cb573ed340766964b2770e7593f129d76afa624e"
"sha2": "0ae1cc9281ef60c31e19985b68713eb40fc2ad2c"
}
,{
"testCaseDescription": "javascript-anonymous-function-replacement-insert-test",
"expectedResult": {
"changes": {
"anonymous-function.js": [
"Added an anonymous(b, c) function",
"Added an anonymous(a, b) function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Added an anonymous(b, c) function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
32
]
}
},
"summary": "Added an anonymous(a, b) function"
}
]
},
"errors": {}
@ -29,19 +71,123 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "cb573ed340766964b2770e7593f129d76afa624e",
"sha1": "0ae1cc9281ef60c31e19985b68713eb40fc2ad2c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4986a49938baf1d287cb567f30c7b2ef9bdd04d0"
"sha2": "e13ea092e21306d5e46e6bf1a2a18566873475d2"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-insert-test",
"expectedResult": {
"changes": {
"anonymous-function.js": [
"Replaced the 'b' identifier with the 'a' identifier",
"Replaced the 'c' identifier with the 'b' identifier",
"Replaced the 'b' identifier with the 'a' identifier",
"Replaced the 'c' identifier with the 'b' identifier"
{
"span": {
"replace": [
{
"start": [
1,
10
],
"end": [
1,
11
]
},
{
"start": [
1,
10
],
"end": [
1,
11
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'a' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
12
],
"end": [
1,
13
]
},
{
"start": [
1,
12
],
"end": [
1,
13
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'b' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
24
],
"end": [
1,
25
]
},
{
"start": [
1,
24
],
"end": [
1,
25
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'a' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
28
],
"end": [
1,
29
]
},
{
"start": [
1,
28
],
"end": [
1,
29
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'b' identifier"
}
]
},
"errors": {}
@ -49,19 +195,123 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "4986a49938baf1d287cb567f30c7b2ef9bdd04d0",
"sha1": "e13ea092e21306d5e46e6bf1a2a18566873475d2",
"gitDir": "test/corpus/repos/javascript",
"sha2": "c74709199029bab1a3e7fd326a1b4332bc0b9381"
"sha2": "664b50f840363802e3fc974ae60831dc4e13d5c2"
}
,{
"testCaseDescription": "javascript-anonymous-function-replacement-test",
"expectedResult": {
"changes": {
"anonymous-function.js": [
"Replaced the 'a' identifier with the 'b' identifier",
"Replaced the 'b' identifier with the 'c' identifier",
"Replaced the 'a' identifier with the 'b' identifier",
"Replaced the 'b' identifier with the 'c' identifier"
{
"span": {
"replace": [
{
"start": [
1,
10
],
"end": [
1,
11
]
},
{
"start": [
1,
10
],
"end": [
1,
11
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'b' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
12
],
"end": [
1,
13
]
},
{
"start": [
1,
12
],
"end": [
1,
13
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'c' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
24
],
"end": [
1,
25
]
},
{
"start": [
1,
24
],
"end": [
1,
25
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'b' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
28
],
"end": [
1,
29
]
},
{
"start": [
1,
28
],
"end": [
1,
29
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'c' identifier"
}
]
},
"errors": {}
@ -69,18 +319,60 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "c74709199029bab1a3e7fd326a1b4332bc0b9381",
"sha1": "664b50f840363802e3fc974ae60831dc4e13d5c2",
"gitDir": "test/corpus/repos/javascript",
"sha2": "745d8324b38294980b7a6b9e62914d330827cdb9"
"sha2": "f0b28a88b5b36ac5eb6770e80f5455c5c2ae3396"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-replacement-test",
"expectedResult": {
"changes": {
"anonymous-function.js": [
"Deleted an anonymous(b, c) function",
"Deleted an anonymous(a, b) function",
"Added an anonymous(b, c) function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Deleted an anonymous(b, c) function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
32
]
}
},
"summary": "Deleted an anonymous(a, b) function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
32
]
}
},
"summary": "Added an anonymous(b, c) function"
}
]
},
"errors": {}
@ -88,16 +380,30 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "745d8324b38294980b7a6b9e62914d330827cdb9",
"sha1": "f0b28a88b5b36ac5eb6770e80f5455c5c2ae3396",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0a97bdf3ba54de75a633542c3baeea9a29ebfc74"
"sha2": "2e8bd85c462e82c1de6ad1d016dec89b8f6c7a94"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-test",
"expectedResult": {
"changes": {
"anonymous-function.js": [
"Deleted an anonymous(a, b) function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Deleted an anonymous(a, b) function"
}
]
},
"errors": {}
@ -105,16 +411,30 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "0a97bdf3ba54de75a633542c3baeea9a29ebfc74",
"sha1": "2e8bd85c462e82c1de6ad1d016dec89b8f6c7a94",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9128b09fb9d9aff67b25d32cb924dcec5023e9a5"
"sha2": "8730cf111655ff909dd1b3a43b8afb78bc05f7b5"
}
,{
"testCaseDescription": "javascript-anonymous-function-delete-rest-test",
"expectedResult": {
"changes": {
"anonymous-function.js": [
"Deleted an anonymous(b, c) function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Deleted an anonymous(b, c) function"
}
]
},
"errors": {}
@ -122,7 +442,7 @@
"filePaths": [
"anonymous-function.js"
],
"sha1": "9128b09fb9d9aff67b25d32cb924dcec5023e9a5",
"sha1": "8730cf111655ff909dd1b3a43b8afb78bc05f7b5",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e5ac882c582e066b576adb9ad39da3ce6dc09be3"
"sha2": "0a29e7e55f31e31e4f830f33dd8b1a6231165888"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"anonymous-parameterless-function.js": [
"Added an anonymous() function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
28
]
}
},
"summary": "Added an anonymous() function"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "e5ac882c582e066b576adb9ad39da3ce6dc09be3",
"sha1": "972c476a86993546e4da7dd3f2c488b455ff24db",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2fc32454f6e4460e35962d014d2e6bcff51e853f"
"sha2": "3e2289ebea24250dc463db0603223b2ad7233e39"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-insert-test",
"expectedResult": {
"changes": {
"anonymous-parameterless-function.js": [
"Added an anonymous() function",
"Added an anonymous() function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
31
]
}
},
"summary": "Added an anonymous() function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
28
]
}
},
"summary": "Added an anonymous() function"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "2fc32454f6e4460e35962d014d2e6bcff51e853f",
"sha1": "3e2289ebea24250dc463db0603223b2ad7233e39",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e45a52db5914e7d588dcc671f508bcb338feeb6e"
"sha2": "281d67dce183a41f664372f47fce3f51b32cdb3a"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-insert-test",
"expectedResult": {
"changes": {
"anonymous-parameterless-function.js": [
"Replaced the 'hello' string with the 'hi' string"
{
"span": {
"replace": [
{
"start": [
1,
21
],
"end": [
1,
28
]
},
{
"start": [
1,
21
],
"end": [
1,
25
]
}
]
},
"summary": "Replaced the 'hello' string with the 'hi' string"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "e45a52db5914e7d588dcc671f508bcb338feeb6e",
"sha1": "281d67dce183a41f664372f47fce3f51b32cdb3a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5b47727177ff9aed9b891b03907c9af0331a781a"
"sha2": "7c730f2014c719d3a12b578babf30f6c2c56c966"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-replacement-test",
"expectedResult": {
"changes": {
"anonymous-parameterless-function.js": [
"Replaced the 'hi' string with the 'hello' string"
{
"span": {
"replace": [
{
"start": [
1,
21
],
"end": [
1,
25
]
},
{
"start": [
1,
21
],
"end": [
1,
28
]
}
]
},
"summary": "Replaced the 'hi' string with the 'hello' string"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "5b47727177ff9aed9b891b03907c9af0331a781a",
"sha1": "7c730f2014c719d3a12b578babf30f6c2c56c966",
"gitDir": "test/corpus/repos/javascript",
"sha2": "186e308a1b740726cd072a3b6820df69df9e5964"
"sha2": "2917edeb872ab9a847651f3df4d3fe0707f410a8"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-replacement-test",
"expectedResult": {
"changes": {
"anonymous-parameterless-function.js": [
"Deleted an anonymous() function",
"Deleted an anonymous() function",
"Added an anonymous() function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
31
]
}
},
"summary": "Deleted an anonymous() function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
28
]
}
},
"summary": "Deleted an anonymous() function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
31
]
}
},
"summary": "Added an anonymous() function"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "186e308a1b740726cd072a3b6820df69df9e5964",
"sha1": "2917edeb872ab9a847651f3df4d3fe0707f410a8",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b682300919787cf58c6f498048aab196a90742e1"
"sha2": "1cc8d6469e2bb265ac93a2c5e75c5a692cf37610"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-test",
"expectedResult": {
"changes": {
"anonymous-parameterless-function.js": [
"Deleted an anonymous() function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
28
]
}
},
"summary": "Deleted an anonymous() function"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "b682300919787cf58c6f498048aab196a90742e1",
"sha1": "1cc8d6469e2bb265ac93a2c5e75c5a692cf37610",
"gitDir": "test/corpus/repos/javascript",
"sha2": "3014ddc3d8f6822d699b62ede940c4fa30b5a22b"
"sha2": "844cb44d31f4dfae4a7f6d71c968c1f7ed98a728"
}
,{
"testCaseDescription": "javascript-anonymous-parameterless-function-delete-rest-test",
"expectedResult": {
"changes": {
"anonymous-parameterless-function.js": [
"Deleted an anonymous() function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
31
]
}
},
"summary": "Deleted an anonymous() function"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"anonymous-parameterless-function.js"
],
"sha1": "3014ddc3d8f6822d699b62ede940c4fa30b5a22b",
"sha1": "844cb44d31f4dfae4a7f6d71c968c1f7ed98a728",
"gitDir": "test/corpus/repos/javascript",
"sha2": "90db4ab800b9884b43e51ab27b8200dcf2e6c3d7"
"sha2": "99592bbf904b69053a764508c8b7e2113f456e77"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"array.js": [
"Added the '[ \"item1\" ]' array"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
12
]
}
},
"summary": "Added the '[ \"item1\" ]' array"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"array.js"
],
"sha1": "fc9aaafb6c12a4fbc174f4a006525bb4b8179e40",
"sha1": "bc7b1f8621267ae931d598deec486fc92bccc736",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d2e6907dbac6e1b5c9c65902da46ad6e42e3b7ed"
"sha2": "1f5c0ab465c11956cade7def7f18df96c823d8d4"
}
,{
"testCaseDescription": "javascript-array-replacement-insert-test",
"expectedResult": {
"changes": {
"array.js": [
"Added the '[ \"item1\", \"item2\" ]' array",
"Added the '[ \"item1\" ]' array"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
21
]
}
},
"summary": "Added the '[ \"item1\", \"item2\" ]' array"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
12
]
}
},
"summary": "Added the '[ \"item1\" ]' array"
}
]
},
"errors": {}
@ -29,16 +71,30 @@
"filePaths": [
"array.js"
],
"sha1": "d2e6907dbac6e1b5c9c65902da46ad6e42e3b7ed",
"sha1": "1f5c0ab465c11956cade7def7f18df96c823d8d4",
"gitDir": "test/corpus/repos/javascript",
"sha2": "74df5e1fcd58290d9b74e938efbd3ff72441f3af"
"sha2": "9eddf6e3cb0a349128bd8900cdf17e43492227da"
}
,{
"testCaseDescription": "javascript-array-delete-insert-test",
"expectedResult": {
"changes": {
"array.js": [
"Deleted the \"item2\" string"
{
"span": {
"delete": {
"start": [
1,
12
],
"end": [
1,
19
]
}
},
"summary": "Deleted the \"item2\" string"
}
]
},
"errors": {}
@ -46,16 +102,30 @@
"filePaths": [
"array.js"
],
"sha1": "74df5e1fcd58290d9b74e938efbd3ff72441f3af",
"sha1": "9eddf6e3cb0a349128bd8900cdf17e43492227da",
"gitDir": "test/corpus/repos/javascript",
"sha2": "eb6dc672f463287b9a8169a2c322274b49bd69ab"
"sha2": "b13b543138e791710292fdf81def6f8d528e8643"
}
,{
"testCaseDescription": "javascript-array-replacement-test",
"expectedResult": {
"changes": {
"array.js": [
"Added the \"item2\" string"
{
"span": {
"insert": {
"start": [
1,
12
],
"end": [
1,
19
]
}
},
"summary": "Added the \"item2\" string"
}
]
},
"errors": {}
@ -63,18 +133,60 @@
"filePaths": [
"array.js"
],
"sha1": "eb6dc672f463287b9a8169a2c322274b49bd69ab",
"sha1": "b13b543138e791710292fdf81def6f8d528e8643",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4936710242fd5737047ea604a6008d2338ee99d8"
"sha2": "4dd191872b1355fdd5afeb5bc36f086b7a7cbd73"
}
,{
"testCaseDescription": "javascript-array-delete-replacement-test",
"expectedResult": {
"changes": {
"array.js": [
"Deleted the '[ \"item1\", \"item2\" ]' array",
"Deleted the '[ \"item1\" ]' array",
"Added the '[ \"item1\", \"item2\" ]' array"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
21
]
}
},
"summary": "Deleted the '[ \"item1\", \"item2\" ]' array"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
12
]
}
},
"summary": "Deleted the '[ \"item1\" ]' array"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
21
]
}
},
"summary": "Added the '[ \"item1\", \"item2\" ]' array"
}
]
},
"errors": {}
@ -82,16 +194,30 @@
"filePaths": [
"array.js"
],
"sha1": "4936710242fd5737047ea604a6008d2338ee99d8",
"sha1": "4dd191872b1355fdd5afeb5bc36f086b7a7cbd73",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4656cfcfa8ae352e1a44eac1652741ef7a517f52"
"sha2": "5434cf6d92267f23a08cf961d1f715d9d67d7611"
}
,{
"testCaseDescription": "javascript-array-delete-test",
"expectedResult": {
"changes": {
"array.js": [
"Deleted the '[ \"item1\" ]' array"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
12
]
}
},
"summary": "Deleted the '[ \"item1\" ]' array"
}
]
},
"errors": {}
@ -99,16 +225,30 @@
"filePaths": [
"array.js"
],
"sha1": "4656cfcfa8ae352e1a44eac1652741ef7a517f52",
"sha1": "5434cf6d92267f23a08cf961d1f715d9d67d7611",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e569fc68e8b4ab3f146846120a82e9bcfd4cb4d3"
"sha2": "d58141388b2aa0186ceb0db2deeeb7524540486a"
}
,{
"testCaseDescription": "javascript-array-delete-rest-test",
"expectedResult": {
"changes": {
"array.js": [
"Deleted the '[ \"item1\", \"item2\" ]' array"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
21
]
}
},
"summary": "Deleted the '[ \"item1\", \"item2\" ]' array"
}
]
},
"errors": {}
@ -116,7 +256,7 @@
"filePaths": [
"array.js"
],
"sha1": "e569fc68e8b4ab3f146846120a82e9bcfd4cb4d3",
"sha1": "d58141388b2aa0186ceb0db2deeeb7524540486a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "86b3a85ea837b41398c1a2d19af1d017c68af6c9"
"sha2": "33c7a858a16464d6fe8e27c69fc09f986fb56dae"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"arrow-function.js": [
"Added an anonymous(f, g) function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
24
]
}
},
"summary": "Added an anonymous(f, g) function"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "4ce1f51b2e48780fc638cd0c98fc3106c6cde070",
"sha1": "b784ecef530da4646deff5aaff5d1263aa216ef3",
"gitDir": "test/corpus/repos/javascript",
"sha2": "821703a22a07e2794ece2d82d2202f04a342e8fa"
"sha2": "b981ec4fb5850f454c25389b3cccdb678e94f626"
}
,{
"testCaseDescription": "javascript-arrow-function-replacement-insert-test",
"expectedResult": {
"changes": {
"arrow-function.js": [
"Added an anonymous(f, g) function",
"Added an anonymous(f, g) function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
24
]
}
},
"summary": "Added an anonymous(f, g) function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
24
]
}
},
"summary": "Added an anonymous(f, g) function"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "821703a22a07e2794ece2d82d2202f04a342e8fa",
"sha1": "b981ec4fb5850f454c25389b3cccdb678e94f626",
"gitDir": "test/corpus/repos/javascript",
"sha2": "bac83bddfc4e4e8be9aa3d491bb3123ec7db5274"
"sha2": "419347ea5418439d6c4a0400799eef9ffe6ef5d2"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-insert-test",
"expectedResult": {
"changes": {
"arrow-function.js": [
"Replaced the 'g' identifier with the 'h' identifier"
{
"span": {
"replace": [
{
"start": [
1,
20
],
"end": [
1,
21
]
},
{
"start": [
1,
20
],
"end": [
1,
21
]
}
]
},
"summary": "Replaced the 'g' identifier with the 'h' identifier"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "bac83bddfc4e4e8be9aa3d491bb3123ec7db5274",
"sha1": "419347ea5418439d6c4a0400799eef9ffe6ef5d2",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4c1ef521eae84257ee7e622902fb821e6d4d72fa"
"sha2": "c427f86b3d74e6605ac82591f26649df704049ce"
}
,{
"testCaseDescription": "javascript-arrow-function-replacement-test",
"expectedResult": {
"changes": {
"arrow-function.js": [
"Replaced the 'h' identifier with the 'g' identifier"
{
"span": {
"replace": [
{
"start": [
1,
20
],
"end": [
1,
21
]
},
{
"start": [
1,
20
],
"end": [
1,
21
]
}
]
},
"summary": "Replaced the 'h' identifier with the 'g' identifier"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "4c1ef521eae84257ee7e622902fb821e6d4d72fa",
"sha1": "c427f86b3d74e6605ac82591f26649df704049ce",
"gitDir": "test/corpus/repos/javascript",
"sha2": "55160b455f7a642e09025c89eb40f4f965c30d61"
"sha2": "89d1b4d2d18912e6cd8a0add7948ee3c8163a399"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-replacement-test",
"expectedResult": {
"changes": {
"arrow-function.js": [
"Deleted an anonymous(f, g) function",
"Deleted an anonymous(f, g) function",
"Added an anonymous(f, g) function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
24
]
}
},
"summary": "Deleted an anonymous(f, g) function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
24
]
}
},
"summary": "Deleted an anonymous(f, g) function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
24
]
}
},
"summary": "Added an anonymous(f, g) function"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "55160b455f7a642e09025c89eb40f4f965c30d61",
"sha1": "89d1b4d2d18912e6cd8a0add7948ee3c8163a399",
"gitDir": "test/corpus/repos/javascript",
"sha2": "796adf890c086e9762bd112d64b8918c12bf31f6"
"sha2": "a77f256f44bf9d478cea9072b568053dfdfd7ff6"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-test",
"expectedResult": {
"changes": {
"arrow-function.js": [
"Deleted an anonymous(f, g) function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
24
]
}
},
"summary": "Deleted an anonymous(f, g) function"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "796adf890c086e9762bd112d64b8918c12bf31f6",
"sha1": "a77f256f44bf9d478cea9072b568053dfdfd7ff6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0e655070e204325433b5664e7d22071b7d7493ab"
"sha2": "aa0b9c6500c4e90003954f42846c897acd910558"
}
,{
"testCaseDescription": "javascript-arrow-function-delete-rest-test",
"expectedResult": {
"changes": {
"arrow-function.js": [
"Deleted an anonymous(f, g) function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
24
]
}
},
"summary": "Deleted an anonymous(f, g) function"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"arrow-function.js"
],
"sha1": "0e655070e204325433b5664e7d22071b7d7493ab",
"sha1": "aa0b9c6500c4e90003954f42846c897acd910558",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5d09bd1d7981c0961505d816d5e38dbbc5abf108"
"sha2": "5a86b9e93eaf41a19163bf18d160b96b37245ee8"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"assignment.js": [
"Added the 'x' assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Added the 'x' assignment"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"assignment.js"
],
"sha1": "71bcd8994bcd93423934dd5b6c7d99c9ed5b26e3",
"sha1": "a561bcb5c9e49680fd9c162c616048bfa100277a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "de5f9dc1dcdd96a2417fd383f4bb2a9dba443af1"
"sha2": "3305579204370d2000328a15830609cd1a3cc048"
}
,{
"testCaseDescription": "javascript-assignment-replacement-insert-test",
"expectedResult": {
"changes": {
"assignment.js": [
"Added the 'x' assignment",
"Added the 'x' assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Added the 'x' assignment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
6
]
}
},
"summary": "Added the 'x' assignment"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"assignment.js"
],
"sha1": "de5f9dc1dcdd96a2417fd383f4bb2a9dba443af1",
"sha1": "3305579204370d2000328a15830609cd1a3cc048",
"gitDir": "test/corpus/repos/javascript",
"sha2": "c64f8c27b2ca1dff37484c94e865ef15164e986a"
"sha2": "6df94e140941a17e62fc44b5695a49949169bfb1"
}
,{
"testCaseDescription": "javascript-assignment-delete-insert-test",
"expectedResult": {
"changes": {
"assignment.js": [
"Replaced '1' with '0' in an assignment to x"
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
6
]
},
{
"start": [
1,
5
],
"end": [
1,
6
]
}
]
},
"summary": "Replaced '1' with '0' in an assignment to x"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"assignment.js"
],
"sha1": "c64f8c27b2ca1dff37484c94e865ef15164e986a",
"sha1": "6df94e140941a17e62fc44b5695a49949169bfb1",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f87b6e125e5684ae65099cb9bdc8a399f67dd7e6"
"sha2": "18468291d2bfbfce6c55fd4786eccde87ccb31f0"
}
,{
"testCaseDescription": "javascript-assignment-replacement-test",
"expectedResult": {
"changes": {
"assignment.js": [
"Replaced '0' with '1' in an assignment to x"
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
6
]
},
{
"start": [
1,
5
],
"end": [
1,
6
]
}
]
},
"summary": "Replaced '0' with '1' in an assignment to x"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"assignment.js"
],
"sha1": "f87b6e125e5684ae65099cb9bdc8a399f67dd7e6",
"sha1": "18468291d2bfbfce6c55fd4786eccde87ccb31f0",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d3f69664891e01d4f36e67fc88a8395374aca17c"
"sha2": "f9256802deb7eee30f243cbf5e99688511ae989e"
}
,{
"testCaseDescription": "javascript-assignment-delete-replacement-test",
"expectedResult": {
"changes": {
"assignment.js": [
"Deleted the 'x' assignment",
"Deleted the 'x' assignment",
"Added the 'x' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Deleted the 'x' assignment"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
6
]
}
},
"summary": "Deleted the 'x' assignment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
6
]
}
},
"summary": "Added the 'x' assignment"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"assignment.js"
],
"sha1": "d3f69664891e01d4f36e67fc88a8395374aca17c",
"sha1": "f9256802deb7eee30f243cbf5e99688511ae989e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e15f1018fc7391002e7edda715329cd7025386d6"
"sha2": "ce267e2a4a95c57f1ccfbc0fb6d86c846a492757"
}
,{
"testCaseDescription": "javascript-assignment-delete-test",
"expectedResult": {
"changes": {
"assignment.js": [
"Deleted the 'x' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Deleted the 'x' assignment"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"assignment.js"
],
"sha1": "e15f1018fc7391002e7edda715329cd7025386d6",
"sha1": "ce267e2a4a95c57f1ccfbc0fb6d86c846a492757",
"gitDir": "test/corpus/repos/javascript",
"sha2": "cb7a79b9470b565802c84867e508baceb33f0abf"
"sha2": "d7d26936a69a2962d5ec0b7b30ce6672df042253"
}
,{
"testCaseDescription": "javascript-assignment-delete-rest-test",
"expectedResult": {
"changes": {
"assignment.js": [
"Deleted the 'x' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Deleted the 'x' assignment"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"assignment.js"
],
"sha1": "cb7a79b9470b565802c84867e508baceb33f0abf",
"sha1": "d7d26936a69a2962d5ec0b7b30ce6672df042253",
"gitDir": "test/corpus/repos/javascript",
"sha2": "36cf72c8436b4fcab0a1f6f85b659b979af0a331"
"sha2": "3b9571c33eac180e0dcf502ffe6eb68757aa50f2"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"bitwise-operator.js": [
"Added the 'i >> j' bitwise operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Added the 'i >> j' bitwise operator"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "0284df48ea6629058a726fcc6df0ab843518cf02",
"sha1": "8d428962767d348a3dbaa62c89eab0564badd448",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7d5276f46f5216ce03aa35a4319444786a054550"
"sha2": "ca679b247a491625e6cadc6a0f3c74eb213024bb"
}
,{
"testCaseDescription": "javascript-bitwise-operator-replacement-insert-test",
"expectedResult": {
"changes": {
"bitwise-operator.js": [
"Added the 'i >> k' bitwise operator",
"Added the 'i >> j' bitwise operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Added the 'i >> k' bitwise operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Added the 'i >> j' bitwise operator"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "7d5276f46f5216ce03aa35a4319444786a054550",
"sha1": "ca679b247a491625e6cadc6a0f3c74eb213024bb",
"gitDir": "test/corpus/repos/javascript",
"sha2": "c875e11424dbab5d621cfdcbebd59b98f42a345b"
"sha2": "58c64d0c5d074267c5363722ac25292b13333b29"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-insert-test",
"expectedResult": {
"changes": {
"bitwise-operator.js": [
"Replaced the 'k' identifier with the 'j' identifier"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
7
]
},
{
"start": [
1,
6
],
"end": [
1,
7
]
}
]
},
"summary": "Replaced the 'k' identifier with the 'j' identifier"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "c875e11424dbab5d621cfdcbebd59b98f42a345b",
"sha1": "58c64d0c5d074267c5363722ac25292b13333b29",
"gitDir": "test/corpus/repos/javascript",
"sha2": "271be4e5b8e728ab3f649290204363132575adff"
"sha2": "3e73c91372d739bfcfceb92cb30be856b0674229"
}
,{
"testCaseDescription": "javascript-bitwise-operator-replacement-test",
"expectedResult": {
"changes": {
"bitwise-operator.js": [
"Replaced the 'j' identifier with the 'k' identifier"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
7
]
},
{
"start": [
1,
6
],
"end": [
1,
7
]
}
]
},
"summary": "Replaced the 'j' identifier with the 'k' identifier"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "271be4e5b8e728ab3f649290204363132575adff",
"sha1": "3e73c91372d739bfcfceb92cb30be856b0674229",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e90a1aac26a6dd5afb5c8f733b768e43b29e93d3"
"sha2": "f5d62f9cf17ccc896f509f6b405805c39f45afc1"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-replacement-test",
"expectedResult": {
"changes": {
"bitwise-operator.js": [
"Deleted the 'i >> k' bitwise operator",
"Deleted the 'i >> j' bitwise operator",
"Added the 'i >> k' bitwise operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'i >> k' bitwise operator"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'i >> j' bitwise operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Added the 'i >> k' bitwise operator"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "e90a1aac26a6dd5afb5c8f733b768e43b29e93d3",
"sha1": "f5d62f9cf17ccc896f509f6b405805c39f45afc1",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b3ba10d7e375e5646d0ae2babeb26a0f9d9c60bd"
"sha2": "db5c1b8fd336475343d489edab9cf0befd5a09d2"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-test",
"expectedResult": {
"changes": {
"bitwise-operator.js": [
"Deleted the 'i >> j' bitwise operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'i >> j' bitwise operator"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "b3ba10d7e375e5646d0ae2babeb26a0f9d9c60bd",
"sha1": "db5c1b8fd336475343d489edab9cf0befd5a09d2",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e1f4a1c4118da33eb87c4789fca0db6161a04c96"
"sha2": "8b532834c43b74f23cdf9da329f8d7d475acecad"
}
,{
"testCaseDescription": "javascript-bitwise-operator-delete-rest-test",
"expectedResult": {
"changes": {
"bitwise-operator.js": [
"Deleted the 'i >> k' bitwise operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'i >> k' bitwise operator"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"bitwise-operator.js"
],
"sha1": "e1f4a1c4118da33eb87c4789fca0db6161a04c96",
"sha1": "8b532834c43b74f23cdf9da329f8d7d475acecad",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b7fa6094450d8736147677929ef398854de0ac66"
"sha2": "1e420171d01e2dca638a5f134f88454bd64d79ae"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"boolean-operator.js": [
"Added the 'i || j' boolean operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Added the 'i || j' boolean operator"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "5e4697c7ee184c7dfdecd9059fc2c5058131cf05",
"sha1": "faaff0e5dd144b090a540e45f9a534c1cceb3ad1",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6c02a1fd47fbf3bd8b21ea5fc04bc032c943c23c"
"sha2": "d6e10ec4014abbcb6b6b338b66eb6f995a232d67"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-insert-test",
"expectedResult": {
"changes": {
"boolean-operator.js": [
"Added the 'i && j' boolean operator",
"Added the 'i || j' boolean operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Added the 'i && j' boolean operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Added the 'i || j' boolean operator"
}
]
},
"errors": {}
@ -29,9 +71,9 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "6c02a1fd47fbf3bd8b21ea5fc04bc032c943c23c",
"sha1": "d6e10ec4014abbcb6b6b338b66eb6f995a232d67",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6040990552afe9c82791b6c97136b1c008110d96"
"sha2": "b09e021bfef5da21754a88b63145c80bc8613308"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-insert-test",
@ -42,9 +84,9 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "6040990552afe9c82791b6c97136b1c008110d96",
"sha1": "b09e021bfef5da21754a88b63145c80bc8613308",
"gitDir": "test/corpus/repos/javascript",
"sha2": "442aeeee3507edad01551f339664c9b98165888b"
"sha2": "3958808a1800344b293b9bc9d432b68041ff5d87"
}
,{
"testCaseDescription": "javascript-boolean-operator-replacement-test",
@ -55,16 +97,30 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "442aeeee3507edad01551f339664c9b98165888b",
"sha1": "3958808a1800344b293b9bc9d432b68041ff5d87",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ba78e28d7b41fb827b99a5bcadcf2fcfcbc1e400"
"sha2": "1625b72ec355c939829455d5397838e0328e6f39"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-replacement-test",
"expectedResult": {
"changes": {
"boolean-operator.js": [
"Deleted the 'i && j' boolean operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'i && j' boolean operator"
}
]
},
"errors": {}
@ -72,16 +128,30 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "ba78e28d7b41fb827b99a5bcadcf2fcfcbc1e400",
"sha1": "1625b72ec355c939829455d5397838e0328e6f39",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ba414b1d960c417802af54e2b76ce81c272c3474"
"sha2": "a4f53d533f7359d95917a22771bc125f137dd311"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-test",
"expectedResult": {
"changes": {
"boolean-operator.js": [
"Deleted the 'i || j' boolean operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'i || j' boolean operator"
}
]
},
"errors": {}
@ -89,16 +159,30 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "ba414b1d960c417802af54e2b76ce81c272c3474",
"sha1": "a4f53d533f7359d95917a22771bc125f137dd311",
"gitDir": "test/corpus/repos/javascript",
"sha2": "bbe07786ae29080753f8e23ada87b82abf2b84e7"
"sha2": "a1e71d859792a4497b9438fe57d0b17847b53184"
}
,{
"testCaseDescription": "javascript-boolean-operator-delete-rest-test",
"expectedResult": {
"changes": {
"boolean-operator.js": [
"Deleted the 'i && j' boolean operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'i && j' boolean operator"
}
]
},
"errors": {}
@ -106,7 +190,7 @@
"filePaths": [
"boolean-operator.js"
],
"sha1": "bbe07786ae29080753f8e23ada87b82abf2b84e7",
"sha1": "a1e71d859792a4497b9438fe57d0b17847b53184",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0284df48ea6629058a726fcc6df0ab843518cf02"
"sha2": "e1dc429edadeaaff5ea72c53fefab478501bdc07"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"chained-callbacks.js": [
"Added the 'this.map(…)' method call"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
39
]
}
},
"summary": "Added the 'this.map(…)' method call"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "5c91d0130fe9174fa613c361cae47758864ea1be",
"sha1": "13cc6ff656f24edfd27ef7cdbbf33198c415c712",
"gitDir": "test/corpus/repos/javascript",
"sha2": "cb8ffbe64d35790639f795037044138216ff1861"
"sha2": "ba8ce3f9c7e869e67a2b1d9ad2b98ea18b349916"
}
,{
"testCaseDescription": "javascript-chained-callbacks-replacement-insert-test",
"expectedResult": {
"changes": {
"chained-callbacks.js": [
"Added the 'this.reduce(…)' method call",
"Added the 'this.map(…)' method call"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
42
]
}
},
"summary": "Added the 'this.reduce(…)' method call"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
39
]
}
},
"summary": "Added the 'this.map(…)' method call"
}
]
},
"errors": {}
@ -29,18 +71,96 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "cb8ffbe64d35790639f795037044138216ff1861",
"sha1": "ba8ce3f9c7e869e67a2b1d9ad2b98ea18b349916",
"gitDir": "test/corpus/repos/javascript",
"sha2": "8fb4a1869c907d4ddc7dace26eb3063b03b0e26c"
"sha2": "d0276aee638ca8e24ee6d91a339544df8fb7eda3"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-insert-test",
"expectedResult": {
"changes": {
"chained-callbacks.js": [
"Replaced the 'reduce' identifier with the 'map' identifier in the this.map(…) method call",
"Replaced the 'b' identifier with the 'a' identifier in the this.map(…) method call",
"Replaced the 'a' identifier with the 'b' identifier in the this.map(…) method call"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
12
]
},
{
"start": [
1,
6
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'reduce' identifier with the 'map' identifier in the this.map(…) method call"
},
{
"span": {
"replace": [
{
"start": [
1,
35
],
"end": [
1,
36
]
},
{
"start": [
1,
32
],
"end": [
1,
33
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'a' identifier in the this.map(…) method call"
},
{
"span": {
"replace": [
{
"start": [
1,
37
],
"end": [
1,
38
]
},
{
"start": [
1,
34
],
"end": [
1,
35
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'b' identifier in the this.map(…) method call"
}
]
},
"errors": {}
@ -48,18 +168,96 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "8fb4a1869c907d4ddc7dace26eb3063b03b0e26c",
"sha1": "d0276aee638ca8e24ee6d91a339544df8fb7eda3",
"gitDir": "test/corpus/repos/javascript",
"sha2": "29724d79a9e1f798d8a12e5ac3fd2ca69071d8f7"
"sha2": "85f3727c68cea10835a214942b66e4d430b73a62"
}
,{
"testCaseDescription": "javascript-chained-callbacks-replacement-test",
"expectedResult": {
"changes": {
"chained-callbacks.js": [
"Replaced the 'map' identifier with the 'reduce' identifier in the this.reduce(…) method call",
"Replaced the 'a' identifier with the 'b' identifier in the this.reduce(…) method call",
"Replaced the 'b' identifier with the 'a' identifier in the this.reduce(…) method call"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
9
]
},
{
"start": [
1,
6
],
"end": [
1,
12
]
}
]
},
"summary": "Replaced the 'map' identifier with the 'reduce' identifier in the this.reduce(…) method call"
},
{
"span": {
"replace": [
{
"start": [
1,
32
],
"end": [
1,
33
]
},
{
"start": [
1,
35
],
"end": [
1,
36
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'b' identifier in the this.reduce(…) method call"
},
{
"span": {
"replace": [
{
"start": [
1,
34
],
"end": [
1,
35
]
},
{
"start": [
1,
37
],
"end": [
1,
38
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'a' identifier in the this.reduce(…) method call"
}
]
},
"errors": {}
@ -67,18 +265,60 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "29724d79a9e1f798d8a12e5ac3fd2ca69071d8f7",
"sha1": "85f3727c68cea10835a214942b66e4d430b73a62",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f7679f3881ef05c60a82c434f49e318b551e6609"
"sha2": "0726997ed14f742f2e3ad23f575cb88aaa5f4b98"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-replacement-test",
"expectedResult": {
"changes": {
"chained-callbacks.js": [
"Deleted the 'this.reduce(…)' method call",
"Deleted the 'this.map(…)' method call",
"Added the 'this.reduce(…)' method call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
42
]
}
},
"summary": "Deleted the 'this.reduce(…)' method call"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
39
]
}
},
"summary": "Deleted the 'this.map(…)' method call"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
42
]
}
},
"summary": "Added the 'this.reduce(…)' method call"
}
]
},
"errors": {}
@ -86,16 +326,30 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "f7679f3881ef05c60a82c434f49e318b551e6609",
"sha1": "0726997ed14f742f2e3ad23f575cb88aaa5f4b98",
"gitDir": "test/corpus/repos/javascript",
"sha2": "52968d06cb3206fcc667f141a58cf73ff8bbdd1d"
"sha2": "db6518a336784be0d8565f2ff963767dffbe22a0"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-test",
"expectedResult": {
"changes": {
"chained-callbacks.js": [
"Deleted the 'this.map(…)' method call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
39
]
}
},
"summary": "Deleted the 'this.map(…)' method call"
}
]
},
"errors": {}
@ -103,16 +357,30 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "52968d06cb3206fcc667f141a58cf73ff8bbdd1d",
"sha1": "db6518a336784be0d8565f2ff963767dffbe22a0",
"gitDir": "test/corpus/repos/javascript",
"sha2": "db7a2bc4cf25fc633efa30adaa7510bcdb945d2d"
"sha2": "f150e07a04ef679de98aa6a19c4e4d534230f7cc"
}
,{
"testCaseDescription": "javascript-chained-callbacks-delete-rest-test",
"expectedResult": {
"changes": {
"chained-callbacks.js": [
"Deleted the 'this.reduce(…)' method call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
42
]
}
},
"summary": "Deleted the 'this.reduce(…)' method call"
}
]
},
"errors": {}
@ -120,7 +388,7 @@
"filePaths": [
"chained-callbacks.js"
],
"sha1": "db7a2bc4cf25fc633efa30adaa7510bcdb945d2d",
"sha1": "f150e07a04ef679de98aa6a19c4e4d534230f7cc",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0a1a0379017da13731e94c9f3675fa6afefcb489"
"sha2": "6b7dd7946b24ba4d49e866944f3bef05c4e948a5"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"chained-property-access.js": [
"Added the 'returned.promise().done(…).fail(…)' return statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
2,
1
]
}
},
"summary": "Added the 'returned.promise().done(…).fail(…)' return statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "3d95b8bc8af09bb93dafc24df379fa1181367357",
"sha1": "d18ce614bfee6bf352af0ace4d200778e8fb4eaf",
"gitDir": "test/corpus/repos/javascript",
"sha2": "23d362cba8c51418f292bdb738273e7288c870b8"
"sha2": "dd59773bcf047bb1a9af4a67c57647d6638492e9"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
2,
1
]
}
},
"summary": "Added the 'returned.promise().done(…).fail(…)' return statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
3,
1
]
}
},
"summary": "Added the 'returned.promise().done(…).fail(…)' return statement"
}
]
},
"errors": {}
@ -29,17 +71,69 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "23d362cba8c51418f292bdb738273e7288c870b8",
"sha1": "dd59773bcf047bb1a9af4a67c57647d6638492e9",
"gitDir": "test/corpus/repos/javascript",
"sha2": "52ee5e317cf6f868f3c726c39fe49dfba7a711a4"
"sha2": "2a35d54700748513ec68ec03f7f5047fac3c1d91"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-insert-test",
"expectedResult": {
"changes": {
"chained-property-access.js": [
"Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…) method call",
"Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…).fail(…) method call"
{
"span": {
"replace": [
{
"start": [
1,
33
],
"end": [
1,
43
]
},
{
"start": [
1,
33
],
"end": [
1,
41
]
}
]
},
"summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…) method call"
},
{
"span": {
"replace": [
{
"start": [
1,
60
],
"end": [
1,
70
]
},
{
"start": [
1,
58
],
"end": [
1,
66
]
}
]
},
"summary": "Replaced the 'otherDefer' identifier with the 'newDefer' identifier in the returned.promise().done(…).fail(…) method call"
}
]
},
"errors": {}
@ -47,17 +141,69 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "52ee5e317cf6f868f3c726c39fe49dfba7a711a4",
"sha1": "2a35d54700748513ec68ec03f7f5047fac3c1d91",
"gitDir": "test/corpus/repos/javascript",
"sha2": "64413497f6c636ec6f3227f6a68b959fe67caa9e"
"sha2": "56c9c8d996ec55dc343c370027e921250704cda2"
}
,{
"testCaseDescription": "javascript-chained-property-access-replacement-test",
"expectedResult": {
"changes": {
"chained-property-access.js": [
"Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…) method call",
"Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…).fail(…) method call"
{
"span": {
"replace": [
{
"start": [
1,
33
],
"end": [
1,
41
]
},
{
"start": [
1,
33
],
"end": [
1,
43
]
}
]
},
"summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…) method call"
},
{
"span": {
"replace": [
{
"start": [
1,
58
],
"end": [
1,
66
]
},
{
"start": [
1,
60
],
"end": [
1,
70
]
}
]
},
"summary": "Replaced the 'newDefer' identifier with the 'otherDefer' identifier in the returned.promise().done(…).fail(…) method call"
}
]
},
"errors": {}
@ -65,18 +211,60 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "64413497f6c636ec6f3227f6a68b959fe67caa9e",
"sha1": "56c9c8d996ec55dc343c370027e921250704cda2",
"gitDir": "test/corpus/repos/javascript",
"sha2": "24f090ce65e5c6fdd821db4ee5d8d5b9d44a464e"
"sha2": "e27981a5a59769ef1b5d5b7d793413ea27df7d90"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-replacement-test",
"expectedResult": {
"changes": {
"chained-property-access.js": [
"Deleted the 'returned.promise().done(…).fail(…)' return statement",
"Deleted the 'returned.promise().done(…).fail(…)' return statement",
"Added the 'returned.promise().done(…).fail(…)' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
2,
1
]
}
},
"summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
3,
1
]
}
},
"summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
3,
1
]
}
},
"summary": "Added the 'returned.promise().done(…).fail(…)' return statement"
}
]
},
"errors": {}
@ -84,16 +272,30 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "24f090ce65e5c6fdd821db4ee5d8d5b9d44a464e",
"sha1": "e27981a5a59769ef1b5d5b7d793413ea27df7d90",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6042a4172d8b35447b0a0e390fea0702fee4edd9"
"sha2": "de1aa8b591a0eba6fc463f536626ac1ea4cba935"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-test",
"expectedResult": {
"changes": {
"chained-property-access.js": [
"Deleted the 'returned.promise().done(…).fail(…)' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
2,
1
]
}
},
"summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement"
}
]
},
"errors": {}
@ -101,16 +303,30 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "6042a4172d8b35447b0a0e390fea0702fee4edd9",
"sha1": "de1aa8b591a0eba6fc463f536626ac1ea4cba935",
"gitDir": "test/corpus/repos/javascript",
"sha2": "c78aa9fb3602cf201cab55a992741f88bd28215e"
"sha2": "4e04595fb1ccf12f0affa9d40a57d54e40b1bb2f"
}
,{
"testCaseDescription": "javascript-chained-property-access-delete-rest-test",
"expectedResult": {
"changes": {
"chained-property-access.js": [
"Deleted the 'returned.promise().done(…).fail(…)' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
2,
1
]
}
},
"summary": "Deleted the 'returned.promise().done(…).fail(…)' return statement"
}
]
},
"errors": {}
@ -118,7 +334,7 @@
"filePaths": [
"chained-property-access.js"
],
"sha1": "c78aa9fb3602cf201cab55a992741f88bd28215e",
"sha1": "4e04595fb1ccf12f0affa9d40a57d54e40b1bb2f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5c91d0130fe9174fa613c361cae47758864ea1be"
"sha2": "0ae29a51ae1d4aa57c5239393081efaf63982b12"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"class.js": [
"Added the 'Foo' class"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
87
]
}
},
"summary": "Added the 'Foo' class"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"class.js"
],
"sha1": "b7f4a89900323bf29bbf4a77720b6321ed5650b0",
"sha1": "d17a2b38a62067233adf6ee07cd8e79c78862e83",
"gitDir": "test/corpus/repos/javascript",
"sha2": "247f8e94e99abd7611aa7a3438d605387a85a43b"
"sha2": "b3c38949d2744c30985b401eeb4a8d5968214038"
}
,{
"testCaseDescription": "javascript-class-replacement-insert-test",
"expectedResult": {
"changes": {
"class.js": [
"Added the 'Foo' class",
"Added the 'Foo' class"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
85
]
}
},
"summary": "Added the 'Foo' class"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
87
]
}
},
"summary": "Added the 'Foo' class"
}
]
},
"errors": {}
@ -29,18 +71,96 @@
"filePaths": [
"class.js"
],
"sha1": "247f8e94e99abd7611aa7a3438d605387a85a43b",
"sha1": "b3c38949d2744c30985b401eeb4a8d5968214038",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4a86897e166419fc0641e9fb78236fd1db2e6e06"
"sha2": "7b2f9b1099f78cc3f7e78764536742adcf9c371f"
}
,{
"testCaseDescription": "javascript-class-delete-insert-test",
"expectedResult": {
"changes": {
"class.js": [
"Replaced the 'foo' identifier with the 'one' identifier in the one method of the 'Foo' class",
"Replaced the 'bar' identifier with the 'two' identifier in the two method of the 'Foo' class",
"Replaced the 'baz' identifier with the 'three' identifier in the three method of the 'Foo' class"
{
"span": {
"replace": [
{
"start": [
1,
20
],
"end": [
1,
23
]
},
{
"start": [
1,
20
],
"end": [
1,
23
]
}
]
},
"summary": "Replaced the 'foo' identifier with the 'one' identifier in the one method of the 'Foo' class"
},
{
"span": {
"replace": [
{
"start": [
1,
42
],
"end": [
1,
45
]
},
{
"start": [
1,
42
],
"end": [
1,
45
]
}
]
},
"summary": "Replaced the 'bar' identifier with the 'two' identifier in the two method of the 'Foo' class"
},
{
"span": {
"replace": [
{
"start": [
1,
63
],
"end": [
1,
66
]
},
{
"start": [
1,
63
],
"end": [
1,
68
]
}
]
},
"summary": "Replaced the 'baz' identifier with the 'three' identifier in the three method of the 'Foo' class"
}
]
},
"errors": {}
@ -48,18 +168,96 @@
"filePaths": [
"class.js"
],
"sha1": "4a86897e166419fc0641e9fb78236fd1db2e6e06",
"sha1": "7b2f9b1099f78cc3f7e78764536742adcf9c371f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "1cc0602d324ac83a8e48bb21015ee4e49b1518b9"
"sha2": "c6b41195ff78d15375ecad210138f106b491c397"
}
,{
"testCaseDescription": "javascript-class-replacement-test",
"expectedResult": {
"changes": {
"class.js": [
"Replaced the 'one' identifier with the 'foo' identifier in the foo method of the 'Foo' class",
"Replaced the 'two' identifier with the 'bar' identifier in the bar method of the 'Foo' class",
"Replaced the 'three' identifier with the 'baz' identifier in the baz method of the 'Foo' class"
{
"span": {
"replace": [
{
"start": [
1,
20
],
"end": [
1,
23
]
},
{
"start": [
1,
20
],
"end": [
1,
23
]
}
]
},
"summary": "Replaced the 'one' identifier with the 'foo' identifier in the foo method of the 'Foo' class"
},
{
"span": {
"replace": [
{
"start": [
1,
42
],
"end": [
1,
45
]
},
{
"start": [
1,
42
],
"end": [
1,
45
]
}
]
},
"summary": "Replaced the 'two' identifier with the 'bar' identifier in the bar method of the 'Foo' class"
},
{
"span": {
"replace": [
{
"start": [
1,
63
],
"end": [
1,
68
]
},
{
"start": [
1,
63
],
"end": [
1,
66
]
}
]
},
"summary": "Replaced the 'three' identifier with the 'baz' identifier in the baz method of the 'Foo' class"
}
]
},
"errors": {}
@ -67,18 +265,60 @@
"filePaths": [
"class.js"
],
"sha1": "1cc0602d324ac83a8e48bb21015ee4e49b1518b9",
"sha1": "c6b41195ff78d15375ecad210138f106b491c397",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2c3cc094d7b46e0d2e0d283aeb649d7b27aed6ae"
"sha2": "72d9f8358863431e6f9ded0aed0877dd974afd24"
}
,{
"testCaseDescription": "javascript-class-delete-replacement-test",
"expectedResult": {
"changes": {
"class.js": [
"Deleted the 'Foo' class",
"Deleted the 'Foo' class",
"Added the 'Foo' class"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
85
]
}
},
"summary": "Deleted the 'Foo' class"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
87
]
}
},
"summary": "Deleted the 'Foo' class"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
85
]
}
},
"summary": "Added the 'Foo' class"
}
]
},
"errors": {}
@ -86,16 +326,30 @@
"filePaths": [
"class.js"
],
"sha1": "2c3cc094d7b46e0d2e0d283aeb649d7b27aed6ae",
"sha1": "72d9f8358863431e6f9ded0aed0877dd974afd24",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e00c85dfe0c63832afc250f883071e5ee865319a"
"sha2": "41fbfe38957d1857423e745ab7cc6af99470141b"
}
,{
"testCaseDescription": "javascript-class-delete-test",
"expectedResult": {
"changes": {
"class.js": [
"Deleted the 'Foo' class"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
87
]
}
},
"summary": "Deleted the 'Foo' class"
}
]
},
"errors": {}
@ -103,16 +357,30 @@
"filePaths": [
"class.js"
],
"sha1": "e00c85dfe0c63832afc250f883071e5ee865319a",
"sha1": "41fbfe38957d1857423e745ab7cc6af99470141b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4741b4a33fe2892275562d2c900cbd49075737e1"
"sha2": "741d75c2f76964d86375e18fb7154936b746410a"
}
,{
"testCaseDescription": "javascript-class-delete-rest-test",
"expectedResult": {
"changes": {
"class.js": [
"Deleted the 'Foo' class"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
85
]
}
},
"summary": "Deleted the 'Foo' class"
}
]
},
"errors": {}
@ -120,7 +388,7 @@
"filePaths": [
"class.js"
],
"sha1": "4741b4a33fe2892275562d2c900cbd49075737e1",
"sha1": "741d75c2f76964d86375e18fb7154936b746410a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "fc9aaafb6c12a4fbc174f4a006525bb4b8179e40"
"sha2": "e3605367f3839bdb67e5ef00ea3be0afdd7d72aa"
}]

View File

@ -3,8 +3,36 @@
"expectedResult": {
"changes": {
"comma-operator.js": [
"Added the 'a' assignment",
"Added the 'b' assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Added the 'a' assignment"
},
{
"span": {
"insert": {
"start": [
1,
8
],
"end": [
1,
13
]
}
},
"summary": "Added the 'b' assignment"
}
]
},
"errors": {}
@ -12,18 +40,60 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "203f8d67079e4651a60594004213482fbcf7da59",
"sha1": "93d092557623a476afac612ad5053ab3e5a63d69",
"gitDir": "test/corpus/repos/javascript",
"sha2": "3b8ee9bc61ab199d982ff74050d4537920ddc3d6"
"sha2": "925d714e520d236f773fd66415cc85d568567c28"
}
,{
"testCaseDescription": "javascript-comma-operator-replacement-insert-test",
"expectedResult": {
"changes": {
"comma-operator.js": [
"Added the 'c' assignment",
"Added the 'a' assignment",
"Added the 'b' assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
23
]
}
},
"summary": "Added the 'c' assignment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
6
]
}
},
"summary": "Added the 'a' assignment"
},
{
"span": {
"insert": {
"start": [
2,
8
],
"end": [
2,
13
]
}
},
"summary": "Added the 'b' assignment"
}
]
},
"errors": {}
@ -31,18 +101,60 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "3b8ee9bc61ab199d982ff74050d4537920ddc3d6",
"sha1": "925d714e520d236f773fd66415cc85d568567c28",
"gitDir": "test/corpus/repos/javascript",
"sha2": "bf6884f1193abbd740737d3b7a4eb6b15fc9259f"
"sha2": "62b94cc1adb6550f6cc3d5487fa0b2fb98f7f64a"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-insert-test",
"expectedResult": {
"changes": {
"comma-operator.js": [
"Added the 'a' assignment",
"Added the 'b' assignment",
"Deleted the 'c' assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Added the 'a' assignment"
},
{
"span": {
"insert": {
"start": [
1,
8
],
"end": [
1,
13
]
}
},
"summary": "Added the 'b' assignment"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
23
]
}
},
"summary": "Deleted the 'c' assignment"
}
]
},
"errors": {}
@ -50,18 +162,60 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "bf6884f1193abbd740737d3b7a4eb6b15fc9259f",
"sha1": "62b94cc1adb6550f6cc3d5487fa0b2fb98f7f64a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "93a8a361ab9d388254c0a3db5983ca3ea45c9eae"
"sha2": "a4b777d2bcbeb98a22c575be5aed21065915ca25"
}
,{
"testCaseDescription": "javascript-comma-operator-replacement-test",
"expectedResult": {
"changes": {
"comma-operator.js": [
"Added the 'c' assignment",
"Deleted the 'a' assignment",
"Deleted the 'b' assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
23
]
}
},
"summary": "Added the 'c' assignment"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Deleted the 'a' assignment"
},
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'b' assignment"
}
]
},
"errors": {}
@ -69,19 +223,75 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "93a8a361ab9d388254c0a3db5983ca3ea45c9eae",
"sha1": "a4b777d2bcbeb98a22c575be5aed21065915ca25",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ae38811e21aa6722976373a05a90ee69691af535"
"sha2": "0044976b6fe9bc1a88363179b05c9164d020d6e0"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-replacement-test",
"expectedResult": {
"changes": {
"comma-operator.js": [
"Deleted the 'c' assignment",
"Deleted the 'a' assignment",
"Deleted the 'b' assignment",
"Added the 'c' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
23
]
}
},
"summary": "Deleted the 'c' assignment"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
6
]
}
},
"summary": "Deleted the 'a' assignment"
},
{
"span": {
"delete": {
"start": [
2,
8
],
"end": [
2,
13
]
}
},
"summary": "Deleted the 'b' assignment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
23
]
}
},
"summary": "Added the 'c' assignment"
}
]
},
"errors": {}
@ -89,17 +299,45 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "ae38811e21aa6722976373a05a90ee69691af535",
"sha1": "0044976b6fe9bc1a88363179b05c9164d020d6e0",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4c2af19db2d11e902b8a404df726346b03991403"
"sha2": "437b6ad23f402553fa54eabc101e1009fe7e90f7"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-test",
"expectedResult": {
"changes": {
"comma-operator.js": [
"Deleted the 'a' assignment",
"Deleted the 'b' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Deleted the 'a' assignment"
},
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'b' assignment"
}
]
},
"errors": {}
@ -107,16 +345,30 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "4c2af19db2d11e902b8a404df726346b03991403",
"sha1": "437b6ad23f402553fa54eabc101e1009fe7e90f7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "988faaa7e2cfc376154ae0e22e4d01e5855a8ee4"
"sha2": "cf7b30999c40f435c936f1ca0dafda480f24624b"
}
,{
"testCaseDescription": "javascript-comma-operator-delete-rest-test",
"expectedResult": {
"changes": {
"comma-operator.js": [
"Deleted the 'c' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
23
]
}
},
"summary": "Deleted the 'c' assignment"
}
]
},
"errors": {}
@ -124,7 +376,7 @@
"filePaths": [
"comma-operator.js"
],
"sha1": "988faaa7e2cfc376154ae0e22e4d01e5855a8ee4",
"sha1": "cf7b30999c40f435c936f1ca0dafda480f24624b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0b57e3c9e5f144a1cce790a12432819561d9d3d3"
"sha2": "b0f399ee205a0929d5082717bdff84b949f064b3"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"comment.js": [
"Added the '// This is a property' comment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Added the '// This is a property' comment"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"comment.js"
],
"sha1": "fea1acf23c86b8d52dd9658d77c6478c2f1113a3",
"sha1": "9966bf3346783a8e39f77cc3b61f8c24f851b0ed",
"gitDir": "test/corpus/repos/javascript",
"sha2": "64e10b9f45aae8cfb288443f59b25d3a951256f0"
"sha2": "0b532cc7ac2078fb6421efad2fba431eebf8b079"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
3,
3
]
}
},
"summary": "Added the '/*\n * This is a method\n*/' comment"
},
{
"span": {
"insert": {
"start": [
4,
1
],
"end": [
4,
22
]
}
},
"summary": "Added the '// This is a property' comment"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"comment.js"
],
"sha1": "64e10b9f45aae8cfb288443f59b25d3a951256f0",
"sha1": "0b532cc7ac2078fb6421efad2fba431eebf8b079",
"gitDir": "test/corpus/repos/javascript",
"sha2": "70fde90c5d4a65db1f350ebf999eb46d816b68ed"
"sha2": "22391ec032d8cf2569c2c79daf9edd535fd5ae1f"
}
,{
"testCaseDescription": "javascript-comment-delete-insert-test",
"expectedResult": {
"changes": {
"comment.js": [
"Replaced the '/*\n * This is a method\n*/' comment with the '// This is a property' comment"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
3,
3
]
},
{
"start": [
1,
1
],
"end": [
1,
22
]
}
]
},
"summary": "Replaced the '/*\n * This is a method\n*/' comment with the '// This is a property' comment"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"comment.js"
],
"sha1": "70fde90c5d4a65db1f350ebf999eb46d816b68ed",
"sha1": "22391ec032d8cf2569c2c79daf9edd535fd5ae1f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d6e49b83077f710e94f40fcb80d4f4f4851eddee"
"sha2": "d2e01036c8e33e37b082368f832c642e1498419d"
}
,{
"testCaseDescription": "javascript-comment-replacement-test",
"expectedResult": {
"changes": {
"comment.js": [
"Replaced the '// This is a property' comment with the '/*\n * This is a method\n*/' comment"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
22
]
},
{
"start": [
1,
1
],
"end": [
3,
3
]
}
]
},
"summary": "Replaced the '// This is a property' comment with the '/*\n * This is a method\n*/' comment"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"comment.js"
],
"sha1": "d6e49b83077f710e94f40fcb80d4f4f4851eddee",
"sha1": "d2e01036c8e33e37b082368f832c642e1498419d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "538bb900566e2532b5790d66ef7517b8436419b7"
"sha2": "53dd565d968e321c83e7d55a640b941ec039ae9d"
}
,{
"testCaseDescription": "javascript-comment-delete-replacement-test",
"expectedResult": {
"changes": {
"comment.js": [
"Deleted the '/*\n * This is a method\n*/' comment",
"Deleted the '// This is a property' comment",
"Added the '/*\n * This is a method\n*/' comment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
3,
3
]
}
},
"summary": "Deleted the '/*\n * This is a method\n*/' comment"
},
{
"span": {
"delete": {
"start": [
4,
1
],
"end": [
4,
22
]
}
},
"summary": "Deleted the '// This is a property' comment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
4,
3
]
}
},
"summary": "Added the '/*\n * This is a method\n*/' comment"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"comment.js"
],
"sha1": "538bb900566e2532b5790d66ef7517b8436419b7",
"sha1": "53dd565d968e321c83e7d55a640b941ec039ae9d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "483cff0560a37de99528d2df3d5082795f541a13"
"sha2": "f44bdb127231af5416f02054c41452de18136eb1"
}
,{
"testCaseDescription": "javascript-comment-delete-test",
"expectedResult": {
"changes": {
"comment.js": [
"Deleted the '// This is a property' comment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
22
]
}
},
"summary": "Deleted the '// This is a property' comment"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"comment.js"
],
"sha1": "483cff0560a37de99528d2df3d5082795f541a13",
"sha1": "f44bdb127231af5416f02054c41452de18136eb1",
"gitDir": "test/corpus/repos/javascript",
"sha2": "00feb18c555bee4313415240b69ad29a8196fb9d"
"sha2": "4d5c2aa9348d27a4efe63e93dd6ea597d1ab60f0"
}
,{
"testCaseDescription": "javascript-comment-delete-rest-test",
"expectedResult": {
"changes": {
"comment.js": [
"Deleted the '/*\n * This is a method\n*/' comment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
3,
3
]
}
},
"summary": "Deleted the '/*\n * This is a method\n*/' comment"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"comment.js"
],
"sha1": "00feb18c555bee4313415240b69ad29a8196fb9d",
"sha1": "4d5c2aa9348d27a4efe63e93dd6ea597d1ab60f0",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9ee63cde4ca79fd99837bf8de8adcd8920b8752b"
"sha2": "d0223efd366c0d9b703a6edf4b9961fa26add3cb"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"constructor-call.js": [
"Added the 'module.Klass(1, \"two\")' constructor"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Added the 'module.Klass(1, \"two\")' constructor"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "ed4d99e2217fe6c9379b70bb164348d6aa21f9fd",
"sha1": "d338b275731ec3d9b527339e1ac1b99f43ea5ea2",
"gitDir": "test/corpus/repos/javascript",
"sha2": "47a794e40c60624e0a4607291234d32c66ac3619"
"sha2": "07f0e420ba82a7a88edead9753bf001dc427c900"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
29
]
}
},
"summary": "Added the 'module.Klass(1, \"three\")' constructor"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
27
]
}
},
"summary": "Added the 'module.Klass(1, \"two\")' constructor"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "47a794e40c60624e0a4607291234d32c66ac3619",
"sha1": "07f0e420ba82a7a88edead9753bf001dc427c900",
"gitDir": "test/corpus/repos/javascript",
"sha2": "807662f63fa3e605780d7177ccab298b17bec0e4"
"sha2": "0ead57e4c68d3441874607df82f10cfae180871c"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-insert-test",
"expectedResult": {
"changes": {
"constructor-call.js": [
"Replaced the \"three\" string with the \"two\" string in the module.Klass(1, \"two\") method call"
{
"span": {
"replace": [
{
"start": [
1,
21
],
"end": [
1,
28
]
},
{
"start": [
1,
21
],
"end": [
1,
26
]
}
]
},
"summary": "Replaced the \"three\" string with the \"two\" string in the module.Klass(1, \"two\") method call"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "807662f63fa3e605780d7177ccab298b17bec0e4",
"sha1": "0ead57e4c68d3441874607df82f10cfae180871c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6eac4923417af6058a1ba7d31ee1279b4a9b31e4"
"sha2": "5312cfad6882b93031aaa4aa6bf94db1cb6097a1"
}
,{
"testCaseDescription": "javascript-constructor-call-replacement-test",
"expectedResult": {
"changes": {
"constructor-call.js": [
"Replaced the \"two\" string with the \"three\" string in the module.Klass(1, \"three\") method call"
{
"span": {
"replace": [
{
"start": [
1,
21
],
"end": [
1,
26
]
},
{
"start": [
1,
21
],
"end": [
1,
28
]
}
]
},
"summary": "Replaced the \"two\" string with the \"three\" string in the module.Klass(1, \"three\") method call"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "6eac4923417af6058a1ba7d31ee1279b4a9b31e4",
"sha1": "5312cfad6882b93031aaa4aa6bf94db1cb6097a1",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9aada6f47f2498dab1143653f37922f043fe4d04"
"sha2": "d1ce2f7e01d8a6fb58e25e00612be76b5a92129b"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-replacement-test",
"expectedResult": {
"changes": {
"constructor-call.js": [
"Deleted the 'module.Klass(1, \"three\")' constructor",
"Deleted the 'module.Klass(1, \"two\")' constructor",
"Added the 'module.Klass(1, \"three\")' constructor"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
29
]
}
},
"summary": "Deleted the 'module.Klass(1, \"three\")' constructor"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
27
]
}
},
"summary": "Deleted the 'module.Klass(1, \"two\")' constructor"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
29
]
}
},
"summary": "Added the 'module.Klass(1, \"three\")' constructor"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "9aada6f47f2498dab1143653f37922f043fe4d04",
"sha1": "d1ce2f7e01d8a6fb58e25e00612be76b5a92129b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0fedb441790310ba8ad5d6eec6caa068db55c70f"
"sha2": "f2947ecde2c4966ba63934c2bf9fadb1bf9494a5"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-test",
"expectedResult": {
"changes": {
"constructor-call.js": [
"Deleted the 'module.Klass(1, \"two\")' constructor"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Deleted the 'module.Klass(1, \"two\")' constructor"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "0fedb441790310ba8ad5d6eec6caa068db55c70f",
"sha1": "f2947ecde2c4966ba63934c2bf9fadb1bf9494a5",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d04c03e6258cd79ad0de4b804e88bc921d11e8b6"
"sha2": "3f2450813b57ef20f48fafa20ec30d660a296e5c"
}
,{
"testCaseDescription": "javascript-constructor-call-delete-rest-test",
"expectedResult": {
"changes": {
"constructor-call.js": [
"Deleted the 'module.Klass(1, \"three\")' constructor"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
29
]
}
},
"summary": "Deleted the 'module.Klass(1, \"three\")' constructor"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"constructor-call.js"
],
"sha1": "d04c03e6258cd79ad0de4b804e88bc921d11e8b6",
"sha1": "3f2450813b57ef20f48fafa20ec30d660a296e5c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "791e48fc86effe144352469c272e5d429d114edc"
"sha2": "d6f65326cb55e5d2b83057d59ae062b3f4bc778e"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"delete-operator.js": [
"Added the 'delete thing['prop']' operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
21
]
}
},
"summary": "Added the 'delete thing['prop']' operator"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "29bb6e3625ec9c3bbd58c6ba514d9f7ebce67705",
"sha1": "660d4f31a366c484dcf287cc129d2236e0064639",
"gitDir": "test/corpus/repos/javascript",
"sha2": "fc7b7737cedcfe37475808336c852098524b6663"
"sha2": "dcdf4363cc41756d111762831febfeb2bc5c3561"
}
,{
"testCaseDescription": "javascript-delete-operator-replacement-insert-test",
"expectedResult": {
"changes": {
"delete-operator.js": [
"Added the 'delete thing.prop' operator",
"Added the 'delete thing['prop']' operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Added the 'delete thing.prop' operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
21
]
}
},
"summary": "Added the 'delete thing['prop']' operator"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "fc7b7737cedcfe37475808336c852098524b6663",
"sha1": "dcdf4363cc41756d111762831febfeb2bc5c3561",
"gitDir": "test/corpus/repos/javascript",
"sha2": "46bb2ef0c6fa7fd218dabdd0e08c543c45c849b8"
"sha2": "b9195fb8317d07798a424a3ad5897669cf2fec4d"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-insert-test",
"expectedResult": {
"changes": {
"delete-operator.js": [
"Replaced the 'delete thing.prop' operator with the 'delete thing['prop']' operator"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
18
]
},
{
"start": [
1,
1
],
"end": [
1,
21
]
}
]
},
"summary": "Replaced the 'delete thing.prop' operator with the 'delete thing['prop']' operator"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "46bb2ef0c6fa7fd218dabdd0e08c543c45c849b8",
"sha1": "b9195fb8317d07798a424a3ad5897669cf2fec4d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0eba89517404842a55b0dffcd216199447022753"
"sha2": "b1aa406089e4aafef90ec5732ba443d1031f561e"
}
,{
"testCaseDescription": "javascript-delete-operator-replacement-test",
"expectedResult": {
"changes": {
"delete-operator.js": [
"Replaced the 'delete thing['prop']' operator with the 'delete thing.prop' operator"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
21
]
},
{
"start": [
1,
1
],
"end": [
1,
18
]
}
]
},
"summary": "Replaced the 'delete thing['prop']' operator with the 'delete thing.prop' operator"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "0eba89517404842a55b0dffcd216199447022753",
"sha1": "b1aa406089e4aafef90ec5732ba443d1031f561e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6ba795157d872cb46f8f35196a05a8a21ad79b78"
"sha2": "3d47f770de2c100cdd3f5cfcb8bc43f582e4a368"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-replacement-test",
"expectedResult": {
"changes": {
"delete-operator.js": [
"Deleted the 'delete thing.prop' operator",
"Deleted the 'delete thing['prop']' operator",
"Added the 'delete thing.prop' operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the 'delete thing.prop' operator"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
21
]
}
},
"summary": "Deleted the 'delete thing['prop']' operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
18
]
}
},
"summary": "Added the 'delete thing.prop' operator"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "6ba795157d872cb46f8f35196a05a8a21ad79b78",
"sha1": "3d47f770de2c100cdd3f5cfcb8bc43f582e4a368",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f1f8139051fd4ffab220822c1c7ae30444c137a4"
"sha2": "79ed3766548499729284c8eb3ff3cecfaed80a4c"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-test",
"expectedResult": {
"changes": {
"delete-operator.js": [
"Deleted the 'delete thing['prop']' operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
21
]
}
},
"summary": "Deleted the 'delete thing['prop']' operator"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "f1f8139051fd4ffab220822c1c7ae30444c137a4",
"sha1": "79ed3766548499729284c8eb3ff3cecfaed80a4c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9f22b99de4edc6fc94a9cfe9f57a2b0cab3c38b6"
"sha2": "3b8b6b7c801a89beb229c8f9b705be4d4465b622"
}
,{
"testCaseDescription": "javascript-delete-operator-delete-rest-test",
"expectedResult": {
"changes": {
"delete-operator.js": [
"Deleted the 'delete thing.prop' operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the 'delete thing.prop' operator"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"delete-operator.js"
],
"sha1": "9f22b99de4edc6fc94a9cfe9f57a2b0cab3c38b6",
"sha1": "3b8b6b7c801a89beb229c8f9b705be4d4465b622",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f2894107b28e50c3ab3c6a0528d509364f55fccc"
"sha2": "8f71c3ee15ecf75d5d1aa9d7f9e82346c26b78e1"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"do-while-statement.js": [
"Added the 'true' do/while statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
42
]
}
},
"summary": "Added the 'true' do/while statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "cf72590c7112ba5cf176106991fc2d91400204fd",
"sha1": "c5a33a05e7c473051b69c27b5268f7e73d9f9818",
"gitDir": "test/corpus/repos/javascript",
"sha2": "85bfd38c0f0525a36678c153805eeaa7a5016f50"
"sha2": "f6d13c24db646eabb87a5569fab5dc059397cd41"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
48
]
}
},
"summary": "Added the 'false' do/while statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
42
]
}
},
"summary": "Added the 'true' do/while statement"
}
]
},
"errors": {}
@ -29,17 +71,69 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "85bfd38c0f0525a36678c153805eeaa7a5016f50",
"sha1": "f6d13c24db646eabb87a5569fab5dc059397cd41",
"gitDir": "test/corpus/repos/javascript",
"sha2": "54f3be668f91e0ef007b093d5daf32d6d5720bea"
"sha2": "b97e52feb5f9b94c2f7c035a5c0b741ab2709c11"
}
,{
"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"
{
"span": {
"replace": [
{
"start": [
1,
18
],
"end": [
1,
29
]
},
{
"start": [
1,
18
],
"end": [
1,
24
]
}
]
},
"summary": "Replaced the 'replacement' identifier with the 'insert' identifier in the console.log(insert) method call"
},
{
"span": {
"replace": [
{
"start": [
1,
41
],
"end": [
1,
46
]
},
{
"start": [
1,
36
],
"end": [
1,
40
]
}
]
},
"summary": "Replaced 'false' with 'true' in the true do/while statement"
}
]
},
"errors": {}
@ -47,17 +141,69 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "54f3be668f91e0ef007b093d5daf32d6d5720bea",
"sha1": "b97e52feb5f9b94c2f7c035a5c0b741ab2709c11",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d35a460230d84f204daaed629262c40a7fa29c54"
"sha2": "618521ec11773660442d22c09e5616569ee0d4d6"
}
,{
"testCaseDescription": "javascript-do-while-statement-replacement-test",
"expectedResult": {
"changes": {
"do-while-statement.js": [
"Replaced the 'insert' identifier with the 'replacement' identifier in the console.log(replacement) method call",
"Replaced 'true' with 'false' in the false do/while statement"
{
"span": {
"replace": [
{
"start": [
1,
18
],
"end": [
1,
24
]
},
{
"start": [
1,
18
],
"end": [
1,
29
]
}
]
},
"summary": "Replaced the 'insert' identifier with the 'replacement' identifier in the console.log(replacement) method call"
},
{
"span": {
"replace": [
{
"start": [
1,
36
],
"end": [
1,
40
]
},
{
"start": [
1,
41
],
"end": [
1,
46
]
}
]
},
"summary": "Replaced 'true' with 'false' in the false do/while statement"
}
]
},
"errors": {}
@ -65,18 +211,60 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "d35a460230d84f204daaed629262c40a7fa29c54",
"sha1": "618521ec11773660442d22c09e5616569ee0d4d6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "81a7fd09b3e449271f35c342f99b8bd0b1ee2d31"
"sha2": "b058c2ef89ec07779649681bb0867d7ca642a924"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-replacement-test",
"expectedResult": {
"changes": {
"do-while-statement.js": [
"Deleted the 'false' do/while statement",
"Deleted the 'true' do/while statement",
"Added the 'false' do/while statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
48
]
}
},
"summary": "Deleted the 'false' do/while statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
42
]
}
},
"summary": "Deleted the 'true' do/while statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
48
]
}
},
"summary": "Added the 'false' do/while statement"
}
]
},
"errors": {}
@ -84,16 +272,30 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "81a7fd09b3e449271f35c342f99b8bd0b1ee2d31",
"sha1": "b058c2ef89ec07779649681bb0867d7ca642a924",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e5a92dbf7de827bd885d594ea8edadd820b9c481"
"sha2": "29a60219132b7497d5f2f2da75cd6fad3583ea3e"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-test",
"expectedResult": {
"changes": {
"do-while-statement.js": [
"Deleted the 'true' do/while statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
42
]
}
},
"summary": "Deleted the 'true' do/while statement"
}
]
},
"errors": {}
@ -101,16 +303,30 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "e5a92dbf7de827bd885d594ea8edadd820b9c481",
"sha1": "29a60219132b7497d5f2f2da75cd6fad3583ea3e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "c08d8ae340b8732869ea58b3f9e2716dc49026aa"
"sha2": "2c0695fb799f92e9549bea04968f0a7db55e5084"
}
,{
"testCaseDescription": "javascript-do-while-statement-delete-rest-test",
"expectedResult": {
"changes": {
"do-while-statement.js": [
"Deleted the 'false' do/while statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
48
]
}
},
"summary": "Deleted the 'false' do/while statement"
}
]
},
"errors": {}
@ -118,7 +334,7 @@
"filePaths": [
"do-while-statement.js"
],
"sha1": "c08d8ae340b8732869ea58b3f9e2716dc49026aa",
"sha1": "2c0695fb799f92e9549bea04968f0a7db55e5084",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2dd2ec7225c40d31a12625d2ed9365654a4134ec"
"sha2": "64789b8e632a3b70997ef3abb4ce031bb19cbedb"
}]

View File

@ -1,267 +0,0 @@
[{
"testCaseDescription": "javascript-export-insert-test",
"expectedResult": {
"changes": {
"export.js": [
"Added the name1, name2, name3, nameN export statement",
"Added the variable1 as name1, variable2 as name2, nameN export statement",
"Added the name1, name2, nameN export statement",
"Added the name1 = value1, name2 = value2, name3, nameN export statement",
"Added the namedFunction export statement",
"Added the anonymous() function export statement",
"Added the name1 export statement",
"Added the name1 as default export statement",
"Added the 'foo' export statement",
"Added the name1, name2, nameN from 'foo' export statement",
"Added the import1 as name1, import2 as name2, nameN from 'bar' export statement",
"Added the 'foo' export statement"
]
},
"errors": {}
},
"filePaths": [
"export.js"
],
"sha1": "fbc5b11fcf02fc81e576ea8ec5d4e590a6a4cf6c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2a02b3c789985c3d109009301b6b75f7151dfa26"
}
,{
"testCaseDescription": "javascript-export-replacement-insert-test",
"expectedResult": {
"changes": {
"export.js": [
"Added the name4, name5, name6, nameZ export statement",
"Added the variable2 as name2, variable3 as name3, nameY export statement",
"Added the name3, name4, nameT export statement",
"Added the name2 = value2, name3 = value3, name4, nameO export statement",
"Added the otherNamedFunction export statement",
"Added the newName1 export statement",
"Added the anonymous() function export statement",
"Added the name2 as statement export statement",
"Added the 'baz' export statement",
"Added the name7, name8, nameP from 'buzz' export statement",
"Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement",
"Added the 'fuzz' export statement",
"Added the name1, name2, name3, nameN export statement",
"Added the variable1 as name1, variable2 as name2, nameN export statement",
"Added the name1, name2, nameN export statement",
"Added the name1 = value1, name2 = value2, name3, nameN export statement",
"Added the namedFunction export statement",
"Added the anonymous() function export statement",
"Added the name1 export statement",
"Added the name1 as default export statement",
"Added the 'foo' export statement",
"Added the name1, name2, nameN from 'foo' export statement",
"Added the import1 as name1, import2 as name2, nameN from 'bar' export statement",
"Added the 'foo' export statement"
]
},
"errors": {}
},
"filePaths": [
"export.js"
],
"sha1": "2a02b3c789985c3d109009301b6b75f7151dfa26",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a86486153befecb5a8435248342ae9ee5f9bb9fe"
}
,{
"testCaseDescription": "javascript-export-delete-insert-test",
"expectedResult": {
"changes": {
"export.js": [
"Replaced the 'name4' identifier with the 'name1' identifier in the name1, name2, name3, nameN export statement",
"Replaced the 'name5' identifier with the 'name2' identifier in the name1, name2, name3, nameN export statement",
"Replaced the 'name6' identifier with the 'name3' identifier in the name1, name2, name3, nameN export statement",
"Replaced the 'nameZ' identifier with the 'nameN' identifier in the name1, name2, name3, nameN export statement",
"Replaced the 'variable2' identifier with the 'variable1' identifier in the variable1 as name1, variable2 as name2, nameN export statement",
"Replaced the 'name2' identifier with the 'name1' identifier in the variable1 as name1, variable2 as name2, nameN export statement",
"Replaced the 'variable3' identifier with the 'variable2' identifier in the variable1 as name1, variable2 as name2, nameN export statement",
"Replaced the 'name3' identifier with the 'name2' identifier in the variable1 as name1, variable2 as name2, nameN export statement",
"Replaced the 'nameY' identifier with the 'nameN' identifier in the variable1 as name1, variable2 as name2, nameN export statement",
"Replaced the 'name3' identifier with the 'name1' identifier in the name1, name2, nameN export statement",
"Replaced the 'name4' identifier with the 'name2' identifier in the name1, name2, nameN export statement",
"Replaced the 'nameT' identifier with the 'nameN' identifier in the name1, name2, nameN export statement",
"Replaced the 'name2' identifier with the 'name1' identifier in the name1 var assignment",
"Replaced the 'value2' identifier with the 'value1' identifier in the name1 var assignment",
"Replaced the 'name3' identifier with the 'name2' identifier in the name2 var assignment",
"Replaced the 'value3' identifier with the 'value2' identifier in the name2 var assignment",
"Replaced the 'name4' identifier with the 'name3' identifier in the name1 = value1, name2 = value2, name3, nameN export statement",
"Replaced the 'nameO' identifier with the 'nameN' identifier in the name1 = value1, name2 = value2, name3, nameN export statement",
"Added the namedFunction export statement",
"Added the anonymous() function export statement",
"Added the name1 export statement",
"Added the name1 as default export statement",
"Replaced the otherNamedFunction export statement with the 'foo' export statement",
"Added the name1, name2, nameN from 'foo' export statement",
"Added the import1 as name1, import2 as name2, nameN from 'bar' export statement",
"Added the 'foo' export statement",
"Deleted the newName1 export statement",
"Deleted the anonymous() function export statement",
"Deleted the name2 as statement export statement",
"Deleted the 'baz' export statement",
"Deleted the name7, name8, nameP from 'buzz' export statement",
"Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement",
"Deleted the 'fuzz' export statement"
]
},
"errors": {}
},
"filePaths": [
"export.js"
],
"sha1": "a86486153befecb5a8435248342ae9ee5f9bb9fe",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7b46f842245529860476386742508d3086628b4b"
}
,{
"testCaseDescription": "javascript-export-replacement-test",
"expectedResult": {
"changes": {
"export.js": [
"Replaced the 'name1' identifier with the 'name4' identifier in the name4, name5, name6, nameZ export statement",
"Replaced the 'name2' identifier with the 'name5' identifier in the name4, name5, name6, nameZ export statement",
"Replaced the 'name3' identifier with the 'name6' identifier in the name4, name5, name6, nameZ export statement",
"Replaced the 'nameN' identifier with the 'nameZ' identifier in the name4, name5, name6, nameZ export statement",
"Added the variable2 as name2, variable3 as name3, nameY export statement",
"Added the name3, name4, nameT export statement",
"Added the name2 = value2, name3 = value3, name4, nameO export statement",
"Added the otherNamedFunction export statement",
"Added the newName1 export statement",
"Added the anonymous() function export statement",
"Added the name2 as statement export statement",
"Added the 'baz' export statement",
"Added the name7, name8, nameP from 'buzz' export statement",
"Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement",
"Added the 'fuzz' export statement",
"Deleted the variable1 as name1, variable2 as name2, nameN export statement",
"Deleted the name1, name2, nameN export statement",
"Deleted the name1 = value1, name2 = value2, name3, nameN export statement",
"Deleted the namedFunction export statement",
"Deleted the anonymous() function export statement",
"Deleted the name1 export statement",
"Deleted the name1 as default export statement",
"Deleted the 'foo' export statement",
"Deleted the name1, name2, nameN from 'foo' export statement",
"Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement",
"Deleted the 'foo' export statement"
]
},
"errors": {}
},
"filePaths": [
"export.js"
],
"sha1": "7b46f842245529860476386742508d3086628b4b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "1586e1f5d610cc2c194478f3aeec506172299c7b"
}
,{
"testCaseDescription": "javascript-export-delete-replacement-test",
"expectedResult": {
"changes": {
"export.js": [
"Deleted the name4, name5, name6, nameZ export statement",
"Deleted the variable2 as name2, variable3 as name3, nameY export statement",
"Deleted the name3, name4, nameT export statement",
"Deleted the name2 = value2, name3 = value3, name4, nameO export statement",
"Deleted the otherNamedFunction export statement",
"Deleted the newName1 export statement",
"Deleted the anonymous() function export statement",
"Deleted the name2 as statement export statement",
"Deleted the 'baz' export statement",
"Deleted the name7, name8, nameP from 'buzz' export statement",
"Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement",
"Deleted the 'fuzz' export statement",
"Deleted the name1, name2, name3, nameN export statement",
"Deleted the variable1 as name1, variable2 as name2, nameN export statement",
"Deleted the name1, name2, nameN export statement",
"Deleted the name1 = value1, name2 = value2, name3, nameN export statement",
"Deleted the namedFunction export statement",
"Deleted the anonymous() function export statement",
"Deleted the name1 export statement",
"Deleted the name1 as default export statement",
"Deleted the 'foo' export statement",
"Deleted the name1, name2, nameN from 'foo' export statement",
"Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement",
"Deleted the 'foo' export statement",
"Added the name4, name5, name6, nameZ export statement",
"Added the variable2 as name2, variable3 as name3, nameY export statement",
"Added the name3, name4, nameT export statement",
"Added the name2 = value2, name3 = value3, name4, nameO export statement",
"Added the otherNamedFunction export statement",
"Added the newName1 export statement",
"Added the anonymous() function export statement",
"Added the name2 as statement export statement",
"Added the 'baz' export statement",
"Added the name7, name8, nameP from 'buzz' export statement",
"Added the import6 as name6, import7 as name7, nameB from 'fizz' export statement",
"Added the 'fuzz' export statement"
]
},
"errors": {}
},
"filePaths": [
"export.js"
],
"sha1": "1586e1f5d610cc2c194478f3aeec506172299c7b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "8ed6038b2ae6a12b88e6139701f2fc038ee2fe60"
}
,{
"testCaseDescription": "javascript-export-delete-test",
"expectedResult": {
"changes": {
"export.js": [
"Deleted the name1, name2, name3, nameN export statement",
"Deleted the variable1 as name1, variable2 as name2, nameN export statement",
"Deleted the name1, name2, nameN export statement",
"Deleted the name1 = value1, name2 = value2, name3, nameN export statement",
"Deleted the namedFunction export statement",
"Deleted the anonymous() function export statement",
"Deleted the name1 export statement",
"Deleted the name1 as default export statement",
"Deleted the 'foo' export statement",
"Deleted the name1, name2, nameN from 'foo' export statement",
"Deleted the import1 as name1, import2 as name2, nameN from 'bar' export statement",
"Deleted the 'foo' export statement"
]
},
"errors": {}
},
"filePaths": [
"export.js"
],
"sha1": "8ed6038b2ae6a12b88e6139701f2fc038ee2fe60",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5fa5440ad72fb78f66fdb8163b2cb7e669a0c9f7"
}
,{
"testCaseDescription": "javascript-export-delete-rest-test",
"expectedResult": {
"changes": {
"export.js": [
"Deleted the name4, name5, name6, nameZ export statement",
"Deleted the variable2 as name2, variable3 as name3, nameY export statement",
"Deleted the name3, name4, nameT export statement",
"Deleted the name2 = value2, name3 = value3, name4, nameO export statement",
"Deleted the otherNamedFunction export statement",
"Deleted the newName1 export statement",
"Deleted the anonymous() function export statement",
"Deleted the name2 as statement export statement",
"Deleted the 'baz' export statement",
"Deleted the name7, name8, nameP from 'buzz' export statement",
"Deleted the import6 as name6, import7 as name7, nameB from 'fizz' export statement",
"Deleted the 'fuzz' export statement"
]
},
"errors": {}
},
"filePaths": [
"export.js"
],
"sha1": "5fa5440ad72fb78f66fdb8163b2cb7e669a0c9f7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "870c7e629a76e123abf0a4f8095499e596838bfd"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"false.js": [
"Added 'false'"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Added 'false'"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"false.js"
],
"sha1": "b8860daa68624499e345ce91a8701d70785b2d4e",
"sha1": "6f781fd1c75a5c824323b66e61fb2717755b4753",
"gitDir": "test/corpus/repos/javascript",
"sha2": "935939abc13ca010fed3c7a42fb22e5eefb20c83"
"sha2": "4973cc5fa83113e784f59efc0e9e2bee97ac8a4d"
}
,{
"testCaseDescription": "javascript-false-replacement-insert-test",
"expectedResult": {
"changes": {
"false.js": [
"Added the 'false' return statement",
"Added 'false'"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
14
]
}
},
"summary": "Added the 'false' return statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
6
]
}
},
"summary": "Added 'false'"
}
]
},
"errors": {}
@ -29,17 +71,45 @@
"filePaths": [
"false.js"
],
"sha1": "935939abc13ca010fed3c7a42fb22e5eefb20c83",
"sha1": "4973cc5fa83113e784f59efc0e9e2bee97ac8a4d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "eb745427af9f88cc5188ffbf490c17bcc0992604"
"sha2": "6bd0e7e033d1921b69c9740f08c5575c7e5e6ee1"
}
,{
"testCaseDescription": "javascript-false-delete-insert-test",
"expectedResult": {
"changes": {
"false.js": [
"Added 'false'",
"Deleted the 'false' return statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Added 'false'"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
14
]
}
},
"summary": "Deleted the 'false' return statement"
}
]
},
"errors": {}
@ -47,17 +117,45 @@
"filePaths": [
"false.js"
],
"sha1": "eb745427af9f88cc5188ffbf490c17bcc0992604",
"sha1": "6bd0e7e033d1921b69c9740f08c5575c7e5e6ee1",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a24851e3e5ded666dca356d08dd559c1eaf6e202"
"sha2": "b2db9c4bb0b3a8d6b68d683e8513b2f6efedb44b"
}
,{
"testCaseDescription": "javascript-false-replacement-test",
"expectedResult": {
"changes": {
"false.js": [
"Added the 'false' return statement",
"Deleted 'false'"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
14
]
}
},
"summary": "Added the 'false' return statement"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Deleted 'false'"
}
]
},
"errors": {}
@ -65,18 +163,60 @@
"filePaths": [
"false.js"
],
"sha1": "a24851e3e5ded666dca356d08dd559c1eaf6e202",
"sha1": "b2db9c4bb0b3a8d6b68d683e8513b2f6efedb44b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "90544cf47a2e57f5a8fb4729b5c302ab8405ada5"
"sha2": "dd9ec604931ffffba1b6c7bd4773ec8ac5418804"
}
,{
"testCaseDescription": "javascript-false-delete-replacement-test",
"expectedResult": {
"changes": {
"false.js": [
"Deleted the 'false' return statement",
"Deleted 'false'",
"Added the 'false' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
14
]
}
},
"summary": "Deleted the 'false' return statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
6
]
}
},
"summary": "Deleted 'false'"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
14
]
}
},
"summary": "Added the 'false' return statement"
}
]
},
"errors": {}
@ -84,16 +224,30 @@
"filePaths": [
"false.js"
],
"sha1": "90544cf47a2e57f5a8fb4729b5c302ab8405ada5",
"sha1": "dd9ec604931ffffba1b6c7bd4773ec8ac5418804",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b3e9f46d88ccfa1baab5f8f6b4473374b80b9d6d"
"sha2": "4b8dddf41a7b9ac76de8ff5eb1327fb0bd1f8dcb"
}
,{
"testCaseDescription": "javascript-false-delete-test",
"expectedResult": {
"changes": {
"false.js": [
"Deleted 'false'"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Deleted 'false'"
}
]
},
"errors": {}
@ -101,16 +255,30 @@
"filePaths": [
"false.js"
],
"sha1": "b3e9f46d88ccfa1baab5f8f6b4473374b80b9d6d",
"sha1": "4b8dddf41a7b9ac76de8ff5eb1327fb0bd1f8dcb",
"gitDir": "test/corpus/repos/javascript",
"sha2": "03ecbd1c9b932527c1cf5cc5fd7219a44d37fa5b"
"sha2": "2f2527a35cc4511ba3e91e4360f61e56f20d9c3e"
}
,{
"testCaseDescription": "javascript-false-delete-rest-test",
"expectedResult": {
"changes": {
"false.js": [
"Deleted the 'false' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
14
]
}
},
"summary": "Deleted the 'false' return statement"
}
]
},
"errors": {}
@ -118,7 +286,7 @@
"filePaths": [
"false.js"
],
"sha1": "03ecbd1c9b932527c1cf5cc5fd7219a44d37fa5b",
"sha1": "2f2527a35cc4511ba3e91e4360f61e56f20d9c3e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b7f4a89900323bf29bbf4a77720b6321ed5650b0"
"sha2": "7f7c1c904ffcc4ea539925a1d336147d84fd90b8"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"for-in-statement.js": [
"Added the 'thing in things' for statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
35
]
}
},
"summary": "Added the 'thing in things' for statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "d595e5cb7bd31790842877e1f7c6f8aee6e2b036",
"sha1": "1e9729897fa1da1617386fa8da290df973dadc93",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f7a3b0774dd21933e462eef6ca1920fb17582c22"
"sha2": "e5d8b7d6f07410e2fa00bbec5718bbdf061166fa"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Added the 'item in items' for statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
35
]
}
},
"summary": "Added the 'thing in things' for statement"
}
]
},
"errors": {}
@ -29,18 +71,96 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "f7a3b0774dd21933e462eef6ca1920fb17582c22",
"sha1": "e5d8b7d6f07410e2fa00bbec5718bbdf061166fa",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7691d04f6704167f72f70e5013fbb9d4d150330b"
"sha2": "6c8ba52447c2faf8fed1eba65cd64c643003461f"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-insert-test",
"expectedResult": {
"changes": {
"for-in-statement.js": [
"Replaced the 'item' identifier with the 'thing' identifier",
"Replaced the 'items' identifier with the 'things' identifier",
"Replaced the 'item' identifier with the 'thing' identifier in the thing() function call"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
10
]
},
{
"start": [
1,
6
],
"end": [
1,
11
]
}
]
},
"summary": "Replaced the 'item' identifier with the 'thing' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
14
],
"end": [
1,
19
]
},
{
"start": [
1,
15
],
"end": [
1,
21
]
}
]
},
"summary": "Replaced the 'items' identifier with the 'things' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
23
],
"end": [
1,
27
]
},
{
"start": [
1,
25
],
"end": [
1,
30
]
}
]
},
"summary": "Replaced the 'item' identifier with the 'thing' identifier in the thing() function call"
}
]
},
"errors": {}
@ -48,18 +168,96 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "7691d04f6704167f72f70e5013fbb9d4d150330b",
"sha1": "6c8ba52447c2faf8fed1eba65cd64c643003461f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "c7457d71148c21ac115cdb6e913ec9e995e7c435"
"sha2": "bc392f77e718987c79b53126053665c245b163ac"
}
,{
"testCaseDescription": "javascript-for-in-statement-replacement-test",
"expectedResult": {
"changes": {
"for-in-statement.js": [
"Replaced the 'thing' identifier with the 'item' identifier",
"Replaced the 'things' identifier with the 'items' identifier",
"Replaced the 'thing' identifier with the 'item' identifier in the item() function call"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
11
]
},
{
"start": [
1,
6
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced the 'thing' identifier with the 'item' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
15
],
"end": [
1,
21
]
},
{
"start": [
1,
14
],
"end": [
1,
19
]
}
]
},
"summary": "Replaced the 'things' identifier with the 'items' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
25
],
"end": [
1,
30
]
},
{
"start": [
1,
23
],
"end": [
1,
27
]
}
]
},
"summary": "Replaced the 'thing' identifier with the 'item' identifier in the item() function call"
}
]
},
"errors": {}
@ -67,18 +265,60 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "c7457d71148c21ac115cdb6e913ec9e995e7c435",
"sha1": "bc392f77e718987c79b53126053665c245b163ac",
"gitDir": "test/corpus/repos/javascript",
"sha2": "1ecb81a174ba8d39619da5e9a68911ead263b1a3"
"sha2": "da2eb693e4cc262362cb81c3fdd040af92eecc42"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-replacement-test",
"expectedResult": {
"changes": {
"for-in-statement.js": [
"Deleted the 'item in items' for statement",
"Deleted the 'thing in things' for statement",
"Added the 'item in items' for statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Deleted the 'item in items' for statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
35
]
}
},
"summary": "Deleted the 'thing in things' for statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
32
]
}
},
"summary": "Added the 'item in items' for statement"
}
]
},
"errors": {}
@ -86,16 +326,30 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "1ecb81a174ba8d39619da5e9a68911ead263b1a3",
"sha1": "da2eb693e4cc262362cb81c3fdd040af92eecc42",
"gitDir": "test/corpus/repos/javascript",
"sha2": "840f3c93ce21ad3025198d721677a2f85da778c0"
"sha2": "210a8ed2aa30b91ca470694492daa7412c616d58"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-test",
"expectedResult": {
"changes": {
"for-in-statement.js": [
"Deleted the 'thing in things' for statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
35
]
}
},
"summary": "Deleted the 'thing in things' for statement"
}
]
},
"errors": {}
@ -103,16 +357,30 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "840f3c93ce21ad3025198d721677a2f85da778c0",
"sha1": "210a8ed2aa30b91ca470694492daa7412c616d58",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b3df6fec9afc59a894ae120888b0799b178447b8"
"sha2": "89852450722771842d4365c760a1403957fc7c96"
}
,{
"testCaseDescription": "javascript-for-in-statement-delete-rest-test",
"expectedResult": {
"changes": {
"for-in-statement.js": [
"Deleted the 'item in items' for statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Deleted the 'item in items' for statement"
}
]
},
"errors": {}
@ -120,7 +388,7 @@
"filePaths": [
"for-in-statement.js"
],
"sha1": "b3df6fec9afc59a894ae120888b0799b178447b8",
"sha1": "89852450722771842d4365c760a1403957fc7c96",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5138a3d72bd9c399737de105fe3d5672dc109bc0"
"sha2": "e572fcdd9abd2fa13fdff57a3afd8b3c43a6c6a0"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"for-loop-with-in-statement.js": [
"Added the 'key in something && i = 0; i < n; i++' for statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
63
]
}
},
"summary": "Added the 'key in something && i = 0; i < n; i++' for statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "b2a12ed6ee90000f320e8bd5b90383e28e847abb",
"sha1": "954a81d340fc574299386d998fb6cd667fe875ce",
"gitDir": "test/corpus/repos/javascript",
"sha2": "15fc343497e8fe5938eb9c3fd38b87c7ea46b261"
"sha2": "8e7957d2f5b2ec1db4345678a2abc67205202d7f"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
73
]
}
},
"summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
63
]
}
},
"summary": "Added the 'key in something && i = 0; i < n; i++' for statement"
}
]
},
"errors": {}
@ -29,17 +71,69 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "15fc343497e8fe5938eb9c3fd38b87c7ea46b261",
"sha1": "8e7957d2f5b2ec1db4345678a2abc67205202d7f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b2a404f8961428ca0653417096d123ff3bd1a945"
"sha2": "8aafa0ba7361d24eecc7b67f364b96fb0e1783d9"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-insert-test",
"expectedResult": {
"changes": {
"for-loop-with-in-statement.js": [
"Replaced the 'otherKey' identifier with the 'key' identifier",
"Replaced the 'doOtherSomething' identifier with the 'doSomething' identifier in the doSomething() function call"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
14
]
},
{
"start": [
1,
6
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'otherKey' identifier with the 'key' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
52
],
"end": [
1,
68
]
},
{
"start": [
1,
47
],
"end": [
1,
58
]
}
]
},
"summary": "Replaced the 'doOtherSomething' identifier with the 'doSomething' identifier in the doSomething() function call"
}
]
},
"errors": {}
@ -47,17 +141,69 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "b2a404f8961428ca0653417096d123ff3bd1a945",
"sha1": "8aafa0ba7361d24eecc7b67f364b96fb0e1783d9",
"gitDir": "test/corpus/repos/javascript",
"sha2": "381a270aa4ebc2ec8ca8a2d6e63149b7c4a5068f"
"sha2": "ba14e6d7fb2d573306e97d6440a31bfd4ba358f7"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-replacement-test",
"expectedResult": {
"changes": {
"for-loop-with-in-statement.js": [
"Replaced the 'key' identifier with the 'otherKey' identifier",
"Replaced the 'doSomething' identifier with the 'doOtherSomething' identifier in the doOtherSomething() function call"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
9
]
},
{
"start": [
1,
6
],
"end": [
1,
14
]
}
]
},
"summary": "Replaced the 'key' identifier with the 'otherKey' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
47
],
"end": [
1,
58
]
},
{
"start": [
1,
52
],
"end": [
1,
68
]
}
]
},
"summary": "Replaced the 'doSomething' identifier with the 'doOtherSomething' identifier in the doOtherSomething() function call"
}
]
},
"errors": {}
@ -65,18 +211,60 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "381a270aa4ebc2ec8ca8a2d6e63149b7c4a5068f",
"sha1": "ba14e6d7fb2d573306e97d6440a31bfd4ba358f7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "656ec5fee935dcce3be715d20ab7514acc6bb356"
"sha2": "99930dbd3a9f28d37aeda9c4746c210df0912e72"
}
,{
"testCaseDescription": "javascript-for-loop-with-in-statement-delete-replacement-test",
"expectedResult": {
"changes": {
"for-loop-with-in-statement.js": [
"Deleted the 'otherKey in something && i = 0; i < n; i++' for statement",
"Deleted the 'key in something && i = 0; i < n; i++' for statement",
"Added the 'otherKey in something && i = 0; i < n; i++' for statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
73
]
}
},
"summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
63
]
}
},
"summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
73
]
}
},
"summary": "Added the 'otherKey in something && i = 0; i < n; i++' for statement"
}
]
},
"errors": {}
@ -84,16 +272,30 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "656ec5fee935dcce3be715d20ab7514acc6bb356",
"sha1": "99930dbd3a9f28d37aeda9c4746c210df0912e72",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2268b9dd8430eb7ac41c6a5043f81b93b4e8ea5e"
"sha2": "eb0f914082b22114ac7e3a487bec4dae17770ebc"
}
,{
"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"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
63
]
}
},
"summary": "Deleted the 'key in something && i = 0; i < n; i++' for statement"
}
]
},
"errors": {}
@ -101,16 +303,30 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "2268b9dd8430eb7ac41c6a5043f81b93b4e8ea5e",
"sha1": "eb0f914082b22114ac7e3a487bec4dae17770ebc",
"gitDir": "test/corpus/repos/javascript",
"sha2": "258415bba988752df58bab7bdd82be3d58aa4084"
"sha2": "d5ae13f5b72c809e77f06665c3eae01cfcf76533"
}
,{
"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"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
73
]
}
},
"summary": "Deleted the 'otherKey in something && i = 0; i < n; i++' for statement"
}
]
},
"errors": {}
@ -118,7 +334,7 @@
"filePaths": [
"for-loop-with-in-statement.js"
],
"sha1": "258415bba988752df58bab7bdd82be3d58aa4084",
"sha1": "d5ae13f5b72c809e77f06665c3eae01cfcf76533",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6fe61c3b39db2dc0038614bb2c9163251c715ef2"
"sha2": "65cf271429cfd2f26c112bf377c0fc4f8d79cba4"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"for-of-statement.js": [
"Added the 'item of items' for statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
43
]
}
},
"summary": "Added the 'item of items' for statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "6fe61c3b39db2dc0038614bb2c9163251c715ef2",
"sha1": "89db44a937a7093bce4f9707fef198d801d1df6c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a21ebf1ac344a3e9221d5832d8df2bf9c872fd01"
"sha2": "2446083ac07858819361d2b6f4d56e5acb211e1f"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
46
]
}
},
"summary": "Added the 'thing of things' for statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
43
]
}
},
"summary": "Added the 'item of items' for statement"
}
]
},
"errors": {}
@ -29,18 +71,96 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "a21ebf1ac344a3e9221d5832d8df2bf9c872fd01",
"sha1": "2446083ac07858819361d2b6f4d56e5acb211e1f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e151eb2bd36bc2d80087a35f04c129623e239d48"
"sha2": "3ef3da8fb378a9e3eb0481df414aeebd601a9c58"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-insert-test",
"expectedResult": {
"changes": {
"for-of-statement.js": [
"Replaced the 'thing' identifier with the 'item' identifier",
"Replaced the 'things' identifier with the 'items' identifier",
"Replaced the 'thing' identifier with the 'item' identifier in the process(item) function call"
{
"span": {
"replace": [
{
"start": [
1,
10
],
"end": [
1,
15
]
},
{
"start": [
1,
10
],
"end": [
1,
14
]
}
]
},
"summary": "Replaced the 'thing' identifier with the 'item' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
19
],
"end": [
1,
25
]
},
{
"start": [
1,
18
],
"end": [
1,
23
]
}
]
},
"summary": "Replaced the 'things' identifier with the 'items' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
37
],
"end": [
1,
42
]
},
{
"start": [
1,
35
],
"end": [
1,
39
]
}
]
},
"summary": "Replaced the 'thing' identifier with the 'item' identifier in the process(item) function call"
}
]
},
"errors": {}
@ -48,18 +168,96 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "e151eb2bd36bc2d80087a35f04c129623e239d48",
"sha1": "3ef3da8fb378a9e3eb0481df414aeebd601a9c58",
"gitDir": "test/corpus/repos/javascript",
"sha2": "3011260f1962c160b49d17e6145c52da647a7fcf"
"sha2": "27d445ebbe6a2d1428363a86b0d8a72f7c3a1fa7"
}
,{
"testCaseDescription": "javascript-for-of-statement-replacement-test",
"expectedResult": {
"changes": {
"for-of-statement.js": [
"Replaced the 'item' identifier with the 'thing' identifier",
"Replaced the 'items' identifier with the 'things' identifier",
"Replaced the 'item' identifier with the 'thing' identifier in the process(thing) function call"
{
"span": {
"replace": [
{
"start": [
1,
10
],
"end": [
1,
14
]
},
{
"start": [
1,
10
],
"end": [
1,
15
]
}
]
},
"summary": "Replaced the 'item' identifier with the 'thing' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
18
],
"end": [
1,
23
]
},
{
"start": [
1,
19
],
"end": [
1,
25
]
}
]
},
"summary": "Replaced the 'items' identifier with the 'things' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
35
],
"end": [
1,
39
]
},
{
"start": [
1,
37
],
"end": [
1,
42
]
}
]
},
"summary": "Replaced the 'item' identifier with the 'thing' identifier in the process(thing) function call"
}
]
},
"errors": {}
@ -67,18 +265,60 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "3011260f1962c160b49d17e6145c52da647a7fcf",
"sha1": "27d445ebbe6a2d1428363a86b0d8a72f7c3a1fa7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4a786f4efe07e3fc733c0d7f392633959513e0d0"
"sha2": "7c22bba4de0d72a6896a92034976544f0cf981d9"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-replacement-test",
"expectedResult": {
"changes": {
"for-of-statement.js": [
"Deleted the 'thing of things' for statement",
"Deleted the 'item of items' for statement",
"Added the 'thing of things' for statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
46
]
}
},
"summary": "Deleted the 'thing of things' for statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
43
]
}
},
"summary": "Deleted the 'item of items' for statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
46
]
}
},
"summary": "Added the 'thing of things' for statement"
}
]
},
"errors": {}
@ -86,16 +326,30 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "4a786f4efe07e3fc733c0d7f392633959513e0d0",
"sha1": "7c22bba4de0d72a6896a92034976544f0cf981d9",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b9b6c4b4ee6e649242b53dddfc502842493b478d"
"sha2": "9a4e4fb16b79c73d23f19d5e01de22370f426681"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-test",
"expectedResult": {
"changes": {
"for-of-statement.js": [
"Deleted the 'item of items' for statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
43
]
}
},
"summary": "Deleted the 'item of items' for statement"
}
]
},
"errors": {}
@ -103,16 +357,30 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "b9b6c4b4ee6e649242b53dddfc502842493b478d",
"sha1": "9a4e4fb16b79c73d23f19d5e01de22370f426681",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e933f875ee956545db127c64851708b47c5d7404"
"sha2": "cf9946632e343e7067c51a06f3e18f62fabbdb54"
}
,{
"testCaseDescription": "javascript-for-of-statement-delete-rest-test",
"expectedResult": {
"changes": {
"for-of-statement.js": [
"Deleted the 'thing of things' for statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
46
]
}
},
"summary": "Deleted the 'thing of things' for statement"
}
]
},
"errors": {}
@ -120,7 +388,7 @@
"filePaths": [
"for-of-statement.js"
],
"sha1": "e933f875ee956545db127c64851708b47c5d7404",
"sha1": "cf9946632e343e7067c51a06f3e18f62fabbdb54",
"gitDir": "test/corpus/repos/javascript",
"sha2": "194fb9e98c554553e25a4f30b4bb5d1fe67a8d21"
"sha2": "67ef9e8da7b64fdbdf370b43e4c780e28ae9efdf"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"for-statement.js": [
"Added the 'i = 0, init(); i < 10; i++' for statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
45
]
}
},
"summary": "Added the 'i = 0, init(); i < 10; i++' for statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"for-statement.js"
],
"sha1": "91879997d6cf416704979ff78f40bbb662d3defc",
"sha1": "de443cf00be9a98ac907413bfb98ae7b8db27831",
"gitDir": "test/corpus/repos/javascript",
"sha2": "1a8ba8d7058b3c21d73f26a26993c935a96f8427"
"sha2": "ee7de8213f031a170e082ef6e72ed09cb1c78ddd"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
46
]
}
},
"summary": "Added the 'i = 0, init(); i < 100; i++' for statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
45
]
}
},
"summary": "Added the 'i = 0, init(); i < 10; i++' for statement"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"for-statement.js"
],
"sha1": "1a8ba8d7058b3c21d73f26a26993c935a96f8427",
"sha1": "ee7de8213f031a170e082ef6e72ed09cb1c78ddd",
"gitDir": "test/corpus/repos/javascript",
"sha2": "8718ed989eb0f1aa579adddc9f239d6d2f7b796b"
"sha2": "3561a122a3823f4dae34a38b8308a08c84dd96f8"
}
,{
"testCaseDescription": "javascript-for-statement-delete-insert-test",
"expectedResult": {
"changes": {
"for-statement.js": [
"Replaced '100' with '10'"
{
"span": {
"replace": [
{
"start": [
1,
25
],
"end": [
1,
28
]
},
{
"start": [
1,
25
],
"end": [
1,
27
]
}
]
},
"summary": "Replaced '100' with '10'"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"for-statement.js"
],
"sha1": "8718ed989eb0f1aa579adddc9f239d6d2f7b796b",
"sha1": "3561a122a3823f4dae34a38b8308a08c84dd96f8",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9cb31bfb46ad81405416bb4f1410ef4b2457c698"
"sha2": "45cc625c20823056b697a08119111b3849855d04"
}
,{
"testCaseDescription": "javascript-for-statement-replacement-test",
"expectedResult": {
"changes": {
"for-statement.js": [
"Replaced '10' with '100'"
{
"span": {
"replace": [
{
"start": [
1,
25
],
"end": [
1,
27
]
},
{
"start": [
1,
25
],
"end": [
1,
28
]
}
]
},
"summary": "Replaced '10' with '100'"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"for-statement.js"
],
"sha1": "9cb31bfb46ad81405416bb4f1410ef4b2457c698",
"sha1": "45cc625c20823056b697a08119111b3849855d04",
"gitDir": "test/corpus/repos/javascript",
"sha2": "bc092c9d40b386eeb155d88f8f331cb9de4382ca"
"sha2": "634af4fd56a8cb4fb227f1505cad159b0aab1036"
}
,{
"testCaseDescription": "javascript-for-statement-delete-replacement-test",
"expectedResult": {
"changes": {
"for-statement.js": [
"Deleted the 'i = 0, init(); i < 100; i++' for statement",
"Deleted the 'i = 0, init(); i < 10; i++' for statement",
"Added the 'i = 0, init(); i < 100; i++' for statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
46
]
}
},
"summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
45
]
}
},
"summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
46
]
}
},
"summary": "Added the 'i = 0, init(); i < 100; i++' for statement"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"for-statement.js"
],
"sha1": "bc092c9d40b386eeb155d88f8f331cb9de4382ca",
"sha1": "634af4fd56a8cb4fb227f1505cad159b0aab1036",
"gitDir": "test/corpus/repos/javascript",
"sha2": "569cdfaca0912eda96a192e4c78c60ec017c321d"
"sha2": "ae4347d2058f6cd47934f4b95215446aaa82b749"
}
,{
"testCaseDescription": "javascript-for-statement-delete-test",
"expectedResult": {
"changes": {
"for-statement.js": [
"Deleted the 'i = 0, init(); i < 10; i++' for statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
45
]
}
},
"summary": "Deleted the 'i = 0, init(); i < 10; i++' for statement"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"for-statement.js"
],
"sha1": "569cdfaca0912eda96a192e4c78c60ec017c321d",
"sha1": "ae4347d2058f6cd47934f4b95215446aaa82b749",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9d50f3a3b47742172e2002721e7d819c5eaab5f0"
"sha2": "aa911951d4d68356f23d3090ab0bddf3d9f5c6f1"
}
,{
"testCaseDescription": "javascript-for-statement-delete-rest-test",
"expectedResult": {
"changes": {
"for-statement.js": [
"Deleted the 'i = 0, init(); i < 100; i++' for statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
46
]
}
},
"summary": "Deleted the 'i = 0, init(); i < 100; i++' for statement"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"for-statement.js"
],
"sha1": "9d50f3a3b47742172e2002721e7d819c5eaab5f0",
"sha1": "aa911951d4d68356f23d3090ab0bddf3d9f5c6f1",
"gitDir": "test/corpus/repos/javascript",
"sha2": "71bcd8994bcd93423934dd5b6c7d99c9ed5b26e3"
"sha2": "4e9ef9bf5e742b75d10cac3498f637ab763b6c99"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"function-call-args.js": [
"Added the 'someFunction(1, \"string\", …, true)' function call"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
77
]
}
},
"summary": "Added the 'someFunction(1, \"string\", …, true)' function call"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"function-call-args.js"
],
"sha1": "53a9c959778b42d9f34bfc266d177a6f1b3065fd",
"sha1": "667c51b29a73971928a1be313c249304f3828099",
"gitDir": "test/corpus/repos/javascript",
"sha2": "69ce469446e795e8a17b33d645fb009a021fccb2"
"sha2": "192575f8455ac438aa0cbfab74d84d4183377778"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
83
]
}
},
"summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
77
]
}
},
"summary": "Added the 'someFunction(1, \"string\", …, true)' function call"
}
]
},
"errors": {}
@ -29,21 +71,177 @@
"filePaths": [
"function-call-args.js"
],
"sha1": "69ce469446e795e8a17b33d645fb009a021fccb2",
"sha1": "192575f8455ac438aa0cbfab74d84d4183377778",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4ac72da22c275527b1e4ef3661a0f5133394e79e"
"sha2": "1acb1db7befa63bf81039b1201e46d1c93f89aa6"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-insert-test",
"expectedResult": {
"changes": {
"function-call-args.js": [
"Replaced the \"otherString\" string with the \"string\" string in the someFunction(1, \"string\", …, true) function call",
"Replaced the 'b' identifier with the 'a' identifier in the someFunction(1, \"string\", …, true) function call",
"Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call",
"Replaced the 'b' identifier with the 'a' identifier in the console.log(a) method call",
"Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call",
"Replaced 'false' with 'true' in the someFunction(1, \"string\", …, true) function call"
{
"span": {
"replace": [
{
"start": [
1,
17
],
"end": [
1,
30
]
},
{
"start": [
1,
17
],
"end": [
1,
25
]
}
]
},
"summary": "Replaced the \"otherString\" string with the \"string\" string in the someFunction(1, \"string\", …, true) function call"
},
{
"span": {
"replace": [
{
"start": [
1,
41
],
"end": [
1,
42
]
},
{
"start": [
1,
36
],
"end": [
1,
37
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'a' identifier in the someFunction(1, \"string\", …, true) function call"
},
{
"span": {
"replace": [
{
"start": [
1,
43
],
"end": [
1,
44
]
},
{
"start": [
1,
38
],
"end": [
1,
39
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call"
},
{
"span": {
"replace": [
{
"start": [
1,
60
],
"end": [
1,
61
]
},
{
"start": [
1,
55
],
"end": [
1,
56
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'a' identifier in the console.log(a) method call"
},
{
"span": {
"replace": [
{
"start": [
1,
71
],
"end": [
1,
72
]
},
{
"start": [
1,
66
],
"end": [
1,
67
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'b' identifier in the someFunction(1, \"string\", …, true) function call"
},
{
"span": {
"replace": [
{
"start": [
1,
77
],
"end": [
1,
82
]
},
{
"start": [
1,
72
],
"end": [
1,
76
]
}
]
},
"summary": "Replaced 'false' with 'true' in the someFunction(1, \"string\", …, true) function call"
}
]
},
"errors": {}
@ -51,21 +249,177 @@
"filePaths": [
"function-call-args.js"
],
"sha1": "4ac72da22c275527b1e4ef3661a0f5133394e79e",
"sha1": "1acb1db7befa63bf81039b1201e46d1c93f89aa6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7c8804faf5e75c6daa02bcff54a4c02bf27bfb6d"
"sha2": "1ef1f93e8742c827b5e36dce1b2a58d084940f00"
}
,{
"testCaseDescription": "javascript-function-call-args-replacement-test",
"expectedResult": {
"changes": {
"function-call-args.js": [
"Replaced the \"string\" string with the \"otherString\" string in the someFunction(1, \"otherString\", …, false) function call",
"Replaced the 'a' identifier with the 'b' identifier in the someFunction(1, \"otherString\", …, false) function call",
"Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call",
"Replaced the 'a' identifier with the 'b' identifier in the console.log(b) method call",
"Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call",
"Replaced 'true' with 'false' in the someFunction(1, \"otherString\", …, false) function call"
{
"span": {
"replace": [
{
"start": [
1,
17
],
"end": [
1,
25
]
},
{
"start": [
1,
17
],
"end": [
1,
30
]
}
]
},
"summary": "Replaced the \"string\" string with the \"otherString\" string in the someFunction(1, \"otherString\", …, false) function call"
},
{
"span": {
"replace": [
{
"start": [
1,
36
],
"end": [
1,
37
]
},
{
"start": [
1,
41
],
"end": [
1,
42
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'b' identifier in the someFunction(1, \"otherString\", …, false) function call"
},
{
"span": {
"replace": [
{
"start": [
1,
38
],
"end": [
1,
39
]
},
{
"start": [
1,
43
],
"end": [
1,
44
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call"
},
{
"span": {
"replace": [
{
"start": [
1,
55
],
"end": [
1,
56
]
},
{
"start": [
1,
60
],
"end": [
1,
61
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'b' identifier in the console.log(b) method call"
},
{
"span": {
"replace": [
{
"start": [
1,
66
],
"end": [
1,
67
]
},
{
"start": [
1,
71
],
"end": [
1,
72
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'c' identifier in the someFunction(1, \"otherString\", …, false) function call"
},
{
"span": {
"replace": [
{
"start": [
1,
72
],
"end": [
1,
76
]
},
{
"start": [
1,
77
],
"end": [
1,
82
]
}
]
},
"summary": "Replaced 'true' with 'false' in the someFunction(1, \"otherString\", …, false) function call"
}
]
},
"errors": {}
@ -73,18 +427,60 @@
"filePaths": [
"function-call-args.js"
],
"sha1": "7c8804faf5e75c6daa02bcff54a4c02bf27bfb6d",
"sha1": "1ef1f93e8742c827b5e36dce1b2a58d084940f00",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2ee20c81efd5d0b72d3288a5a7b8d9e46a9dcfa8"
"sha2": "9610dd7ef8edff8b65d81c889cb22aa5efb67019"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-replacement-test",
"expectedResult": {
"changes": {
"function-call-args.js": [
"Deleted the 'someFunction(1, \"otherString\", …, false)' function call",
"Deleted the 'someFunction(1, \"string\", …, true)' function call",
"Added the 'someFunction(1, \"otherString\", …, false)' function call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
83
]
}
},
"summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
77
]
}
},
"summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
83
]
}
},
"summary": "Added the 'someFunction(1, \"otherString\", …, false)' function call"
}
]
},
"errors": {}
@ -92,16 +488,30 @@
"filePaths": [
"function-call-args.js"
],
"sha1": "2ee20c81efd5d0b72d3288a5a7b8d9e46a9dcfa8",
"sha1": "9610dd7ef8edff8b65d81c889cb22aa5efb67019",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f7edc7317b631ea59eed37c07c3efdf5e84147d7"
"sha2": "ad2d4d347fb4551d07b8970a27634569e6f9b789"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-test",
"expectedResult": {
"changes": {
"function-call-args.js": [
"Deleted the 'someFunction(1, \"string\", …, true)' function call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
77
]
}
},
"summary": "Deleted the 'someFunction(1, \"string\", …, true)' function call"
}
]
},
"errors": {}
@ -109,16 +519,30 @@
"filePaths": [
"function-call-args.js"
],
"sha1": "f7edc7317b631ea59eed37c07c3efdf5e84147d7",
"sha1": "ad2d4d347fb4551d07b8970a27634569e6f9b789",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9b54db4c381da21bca30ea193686763943336c3e"
"sha2": "953921a66be0d1ed61bf4db6884cd0ad0a057f07"
}
,{
"testCaseDescription": "javascript-function-call-args-delete-rest-test",
"expectedResult": {
"changes": {
"function-call-args.js": [
"Deleted the 'someFunction(1, \"otherString\", …, false)' function call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
83
]
}
},
"summary": "Deleted the 'someFunction(1, \"otherString\", …, false)' function call"
}
]
},
"errors": {}
@ -126,7 +550,7 @@
"filePaths": [
"function-call-args.js"
],
"sha1": "9b54db4c381da21bca30ea193686763943336c3e",
"sha1": "953921a66be0d1ed61bf4db6884cd0ad0a057f07",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ed4d99e2217fe6c9379b70bb164348d6aa21f9fd"
"sha2": "6f3b3d0ccb1f85f9dd79220ea588b11e540d7290"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"function-call.js": [
"Added the 'someFunction(arg1, \"arg2\")' function call"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Added the 'someFunction(arg1, \"arg2\")' function call"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"function-call.js"
],
"sha1": "0a1a0379017da13731e94c9f3675fa6afefcb489",
"sha1": "4b213c3b88b5e8aace51dfa0379aaa8de01536b8",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d3dfc8794ef412b6704bfdb9ff77090a2785e3a2"
"sha2": "77cb0c7af7488197be59308f1296a909bd4dc5b6"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Added the 'someFunction(arg1, \"arg3\")' function call"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
27
]
}
},
"summary": "Added the 'someFunction(arg1, \"arg2\")' function call"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"function-call.js"
],
"sha1": "d3dfc8794ef412b6704bfdb9ff77090a2785e3a2",
"sha1": "77cb0c7af7488197be59308f1296a909bd4dc5b6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2b088cef679e7fb39486e18d646881ead2936f55"
"sha2": "1b4585f4d837d2412aa2349b729616df4be4dfc3"
}
,{
"testCaseDescription": "javascript-function-call-delete-insert-test",
"expectedResult": {
"changes": {
"function-call.js": [
"Replaced the \"arg3\" string with the \"arg2\" string in the someFunction(arg1, \"arg2\") function call"
{
"span": {
"replace": [
{
"start": [
1,
20
],
"end": [
1,
26
]
},
{
"start": [
1,
20
],
"end": [
1,
26
]
}
]
},
"summary": "Replaced the \"arg3\" string with the \"arg2\" string in the someFunction(arg1, \"arg2\") function call"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"function-call.js"
],
"sha1": "2b088cef679e7fb39486e18d646881ead2936f55",
"sha1": "1b4585f4d837d2412aa2349b729616df4be4dfc3",
"gitDir": "test/corpus/repos/javascript",
"sha2": "654a4b909737feb4736bb41374026ef497853455"
"sha2": "ff9cd97499db7659134fc3f9c3eede631ffcf43b"
}
,{
"testCaseDescription": "javascript-function-call-replacement-test",
"expectedResult": {
"changes": {
"function-call.js": [
"Replaced the \"arg2\" string with the \"arg3\" string in the someFunction(arg1, \"arg3\") function call"
{
"span": {
"replace": [
{
"start": [
1,
20
],
"end": [
1,
26
]
},
{
"start": [
1,
20
],
"end": [
1,
26
]
}
]
},
"summary": "Replaced the \"arg2\" string with the \"arg3\" string in the someFunction(arg1, \"arg3\") function call"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"function-call.js"
],
"sha1": "654a4b909737feb4736bb41374026ef497853455",
"sha1": "ff9cd97499db7659134fc3f9c3eede631ffcf43b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "fa690ce0ead87e535c157e23d5f12eedbc0607ed"
"sha2": "40ae68e40bb296a0fed10ad139a32c0bdd48c91d"
}
,{
"testCaseDescription": "javascript-function-call-delete-replacement-test",
"expectedResult": {
"changes": {
"function-call.js": [
"Deleted the 'someFunction(arg1, \"arg3\")' function call",
"Deleted the 'someFunction(arg1, \"arg2\")' function call",
"Added the 'someFunction(arg1, \"arg3\")' function call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
27
]
}
},
"summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
27
]
}
},
"summary": "Added the 'someFunction(arg1, \"arg3\")' function call"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"function-call.js"
],
"sha1": "fa690ce0ead87e535c157e23d5f12eedbc0607ed",
"sha1": "40ae68e40bb296a0fed10ad139a32c0bdd48c91d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d8dec8d2b7c270327330880ced89b965a166e3c0"
"sha2": "97b784a48b8ba2ab17d9fb5e690fdd5e27995053"
}
,{
"testCaseDescription": "javascript-function-call-delete-test",
"expectedResult": {
"changes": {
"function-call.js": [
"Deleted the 'someFunction(arg1, \"arg2\")' function call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Deleted the 'someFunction(arg1, \"arg2\")' function call"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"function-call.js"
],
"sha1": "d8dec8d2b7c270327330880ced89b965a166e3c0",
"sha1": "97b784a48b8ba2ab17d9fb5e690fdd5e27995053",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4454bbceb4ef680a7b9ffa2d68368e7f8d85c2f8"
"sha2": "4ab24690a7b34511675eb6c179c5b85a382c7952"
}
,{
"testCaseDescription": "javascript-function-call-delete-rest-test",
"expectedResult": {
"changes": {
"function-call.js": [
"Deleted the 'someFunction(arg1, \"arg3\")' function call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
27
]
}
},
"summary": "Deleted the 'someFunction(arg1, \"arg3\")' function call"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"function-call.js"
],
"sha1": "4454bbceb4ef680a7b9ffa2d68368e7f8d85c2f8",
"sha1": "4ab24690a7b34511675eb6c179c5b85a382c7952",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5e933ecc7f1454b396bd04022556601bcf8de7ab"
"sha2": "35a769b31d29eac1dc0307402e6e2698e71177ac"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"function.js": [
"Added an anonymous(arg1, arg2) function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
31
]
}
},
"summary": "Added an anonymous(arg1, arg2) function"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"function.js"
],
"sha1": "86b3a85ea837b41398c1a2d19af1d017c68af6c9",
"sha1": "9cd120dd3b152d83f8eea69dfe22940d1acbf177",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9fc2b72a190bc6da6133993fd62a6a9cc147950b"
"sha2": "654ce2cc1260f48fb82edbd0cc5926f11c877700"
}
,{
"testCaseDescription": "javascript-function-replacement-insert-test",
"expectedResult": {
"changes": {
"function.js": [
"Added an anonymous(arg1, arg2) function",
"Added an anonymous(arg1, arg2) function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
31
]
}
},
"summary": "Added an anonymous(arg1, arg2) function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
31
]
}
},
"summary": "Added an anonymous(arg1, arg2) function"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"function.js"
],
"sha1": "9fc2b72a190bc6da6133993fd62a6a9cc147950b",
"sha1": "654ce2cc1260f48fb82edbd0cc5926f11c877700",
"gitDir": "test/corpus/repos/javascript",
"sha2": "cdff7900834a6cc6f3e68f70820a1e419e5ff27e"
"sha2": "d935758b74f8e47e1475010591b39e545d5ecc7a"
}
,{
"testCaseDescription": "javascript-function-delete-insert-test",
"expectedResult": {
"changes": {
"function.js": [
"Replaced the 'arg1' identifier with the 'arg2' identifier"
{
"span": {
"replace": [
{
"start": [
1,
24
],
"end": [
1,
28
]
},
{
"start": [
1,
24
],
"end": [
1,
28
]
}
]
},
"summary": "Replaced the 'arg1' identifier with the 'arg2' identifier"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"function.js"
],
"sha1": "cdff7900834a6cc6f3e68f70820a1e419e5ff27e",
"sha1": "d935758b74f8e47e1475010591b39e545d5ecc7a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "beab8a8b934ab1a609d5cb895a2e9a6162536d30"
"sha2": "8c1abbc8823d22df989efd04e0bcc27c2342b00d"
}
,{
"testCaseDescription": "javascript-function-replacement-test",
"expectedResult": {
"changes": {
"function.js": [
"Replaced the 'arg2' identifier with the 'arg1' identifier"
{
"span": {
"replace": [
{
"start": [
1,
24
],
"end": [
1,
28
]
},
{
"start": [
1,
24
],
"end": [
1,
28
]
}
]
},
"summary": "Replaced the 'arg2' identifier with the 'arg1' identifier"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"function.js"
],
"sha1": "beab8a8b934ab1a609d5cb895a2e9a6162536d30",
"sha1": "8c1abbc8823d22df989efd04e0bcc27c2342b00d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f120d073ae48393fd611a3c91878eb43f762c481"
"sha2": "0dbbe59af8673a1a5d7ef30f3feed1d050360f91"
}
,{
"testCaseDescription": "javascript-function-delete-replacement-test",
"expectedResult": {
"changes": {
"function.js": [
"Deleted an anonymous(arg1, arg2) function",
"Deleted an anonymous(arg1, arg2) function",
"Added an anonymous(arg1, arg2) function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
31
]
}
},
"summary": "Deleted an anonymous(arg1, arg2) function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
31
]
}
},
"summary": "Deleted an anonymous(arg1, arg2) function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
31
]
}
},
"summary": "Added an anonymous(arg1, arg2) function"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"function.js"
],
"sha1": "f120d073ae48393fd611a3c91878eb43f762c481",
"sha1": "0dbbe59af8673a1a5d7ef30f3feed1d050360f91",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9cad6f984d6002543e2d275b0ef06d80d2518730"
"sha2": "aae7da5266e45976f3617b3d9068bbba2b814869"
}
,{
"testCaseDescription": "javascript-function-delete-test",
"expectedResult": {
"changes": {
"function.js": [
"Deleted an anonymous(arg1, arg2) function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
31
]
}
},
"summary": "Deleted an anonymous(arg1, arg2) function"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"function.js"
],
"sha1": "9cad6f984d6002543e2d275b0ef06d80d2518730",
"sha1": "aae7da5266e45976f3617b3d9068bbba2b814869",
"gitDir": "test/corpus/repos/javascript",
"sha2": "108986a94a3b034f599ca41c93ec14c116abfa79"
"sha2": "183393122ec9e9b0bc8b67482c0435aec3fa76a6"
}
,{
"testCaseDescription": "javascript-function-delete-rest-test",
"expectedResult": {
"changes": {
"function.js": [
"Deleted an anonymous(arg1, arg2) function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
31
]
}
},
"summary": "Deleted an anonymous(arg1, arg2) function"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"function.js"
],
"sha1": "108986a94a3b034f599ca41c93ec14c116abfa79",
"sha1": "183393122ec9e9b0bc8b67482c0435aec3fa76a6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4ce1f51b2e48780fc638cd0c98fc3106c6cde070"
"sha2": "f0f1ee84b62e5f9e91523c1e29c3469ab06fefdf"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"generator-function.js": [
"Added the 'generateStuff' function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
59
]
}
},
"summary": "Added the 'generateStuff' function"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"generator-function.js"
],
"sha1": "5d09bd1d7981c0961505d816d5e38dbbc5abf108",
"sha1": "5190dfa16aab4d1416b5dad47a3f9cc704af1fae",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b055cb9d04d11e4a9bc2b022e9d99983a2780499"
"sha2": "d7eb5084f8ee88c7b9f3657c9c05d72e4329c5c7"
}
,{
"testCaseDescription": "javascript-generator-function-replacement-insert-test",
"expectedResult": {
"changes": {
"generator-function.js": [
"Added the 'generateNewStuff' function",
"Added the 'generateStuff' function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
62
]
}
},
"summary": "Added the 'generateNewStuff' function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
59
]
}
},
"summary": "Added the 'generateStuff' function"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"generator-function.js"
],
"sha1": "b055cb9d04d11e4a9bc2b022e9d99983a2780499",
"sha1": "d7eb5084f8ee88c7b9f3657c9c05d72e4329c5c7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e4fbac763d5e8f5f310a8a3d7a6f8d840619174e"
"sha2": "9a1ba4ab7ac42607d9eacb0e871763a2bfe06221"
}
,{
"testCaseDescription": "javascript-generator-function-delete-insert-test",
"expectedResult": {
"changes": {
"generator-function.js": [
"Replaced the 'generateNewStuff' identifier with the 'generateStuff' identifier in the generateStuff function"
{
"span": {
"replace": [
{
"start": [
1,
11
],
"end": [
1,
27
]
},
{
"start": [
1,
11
],
"end": [
1,
24
]
}
]
},
"summary": "Replaced the 'generateNewStuff' identifier with the 'generateStuff' identifier in the generateStuff function"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"generator-function.js"
],
"sha1": "e4fbac763d5e8f5f310a8a3d7a6f8d840619174e",
"sha1": "9a1ba4ab7ac42607d9eacb0e871763a2bfe06221",
"gitDir": "test/corpus/repos/javascript",
"sha2": "67675547b9d2599c68941be313ecd7b888932388"
"sha2": "7ed14c167f2304005ed80d19a4019dfe9b3d9818"
}
,{
"testCaseDescription": "javascript-generator-function-replacement-test",
"expectedResult": {
"changes": {
"generator-function.js": [
"Replaced the 'generateStuff' identifier with the 'generateNewStuff' identifier in the generateNewStuff function"
{
"span": {
"replace": [
{
"start": [
1,
11
],
"end": [
1,
24
]
},
{
"start": [
1,
11
],
"end": [
1,
27
]
}
]
},
"summary": "Replaced the 'generateStuff' identifier with the 'generateNewStuff' identifier in the generateNewStuff function"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"generator-function.js"
],
"sha1": "67675547b9d2599c68941be313ecd7b888932388",
"sha1": "7ed14c167f2304005ed80d19a4019dfe9b3d9818",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f2eb336805f01fefe41442565fb61ac7fc5dd6d2"
"sha2": "fd15cd2ea8a79ab44aefbe49e0cefa5d77567210"
}
,{
"testCaseDescription": "javascript-generator-function-delete-replacement-test",
"expectedResult": {
"changes": {
"generator-function.js": [
"Deleted the 'generateNewStuff' function",
"Deleted the 'generateStuff' function",
"Added the 'generateNewStuff' function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
62
]
}
},
"summary": "Deleted the 'generateNewStuff' function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
59
]
}
},
"summary": "Deleted the 'generateStuff' function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
62
]
}
},
"summary": "Added the 'generateNewStuff' function"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"generator-function.js"
],
"sha1": "f2eb336805f01fefe41442565fb61ac7fc5dd6d2",
"sha1": "fd15cd2ea8a79ab44aefbe49e0cefa5d77567210",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e11effe73e343fdac5157f9062aab8190ba1041c"
"sha2": "f7461e2154cb8c35bd33d73880ac8ce6fed13968"
}
,{
"testCaseDescription": "javascript-generator-function-delete-test",
"expectedResult": {
"changes": {
"generator-function.js": [
"Deleted the 'generateStuff' function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
59
]
}
},
"summary": "Deleted the 'generateStuff' function"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"generator-function.js"
],
"sha1": "e11effe73e343fdac5157f9062aab8190ba1041c",
"sha1": "f7461e2154cb8c35bd33d73880ac8ce6fed13968",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6e14135d5d47798b0b683769a3269a4812ad15b9"
"sha2": "d6e72611d7be249f33d8283e3fd246ba10119a64"
}
,{
"testCaseDescription": "javascript-generator-function-delete-rest-test",
"expectedResult": {
"changes": {
"generator-function.js": [
"Deleted the 'generateNewStuff' function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
62
]
}
},
"summary": "Deleted the 'generateNewStuff' function"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"generator-function.js"
],
"sha1": "6e14135d5d47798b0b683769a3269a4812ad15b9",
"sha1": "d6e72611d7be249f33d8283e3fd246ba10119a64",
"gitDir": "test/corpus/repos/javascript",
"sha2": "12ad7dc9f0bac8d9da1560cc4e1b965b0a04f159"
"sha2": "dac1b3637553f83bfd1567e914a0236f9b41b9ec"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"identifier.js": [
"Added the 'theVar' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Added the 'theVar' identifier"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"identifier.js"
],
"sha1": "b3b641ed7deb3f41fd97836c9026ce33eeba4a48",
"sha1": "49074a4800a61fa651152d1ed712c66519fafbeb",
"gitDir": "test/corpus/repos/javascript",
"sha2": "860e6cb5f10c84e6aac3953151b5ebec56ab3312"
"sha2": "7c6643be086c41a5cd376fbf7b36e2f7d33bc1bf"
}
,{
"testCaseDescription": "javascript-identifier-replacement-insert-test",
"expectedResult": {
"changes": {
"identifier.js": [
"Added the 'theVar2' identifier",
"Added the 'theVar' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Added the 'theVar2' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Added the 'theVar' identifier"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"identifier.js"
],
"sha1": "860e6cb5f10c84e6aac3953151b5ebec56ab3312",
"sha1": "7c6643be086c41a5cd376fbf7b36e2f7d33bc1bf",
"gitDir": "test/corpus/repos/javascript",
"sha2": "392eb6b25b6edd2cc3cad0293066ad0f330cc72f"
"sha2": "9714f432aec25fb2318e2dab9f9b2a78fc5cb22f"
}
,{
"testCaseDescription": "javascript-identifier-delete-insert-test",
"expectedResult": {
"changes": {
"identifier.js": [
"Replaced the 'theVar2' identifier with the 'theVar' identifier"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
8
]
},
{
"start": [
1,
1
],
"end": [
1,
7
]
}
]
},
"summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"identifier.js"
],
"sha1": "392eb6b25b6edd2cc3cad0293066ad0f330cc72f",
"sha1": "9714f432aec25fb2318e2dab9f9b2a78fc5cb22f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2179a48c2b6e7200e0a34f33e20e3d1efe2ae34a"
"sha2": "93fd36c156a2e1bd23e2e5777f4b5b7e7a82c7cb"
}
,{
"testCaseDescription": "javascript-identifier-replacement-test",
"expectedResult": {
"changes": {
"identifier.js": [
"Replaced the 'theVar' identifier with the 'theVar2' identifier"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
7
]
},
{
"start": [
1,
1
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"identifier.js"
],
"sha1": "2179a48c2b6e7200e0a34f33e20e3d1efe2ae34a",
"sha1": "93fd36c156a2e1bd23e2e5777f4b5b7e7a82c7cb",
"gitDir": "test/corpus/repos/javascript",
"sha2": "43486e90c660f961f930e3e22143865875bcd5ff"
"sha2": "cfb79cbb2bcd620edb55c909983e5e631a08c863"
}
,{
"testCaseDescription": "javascript-identifier-delete-replacement-test",
"expectedResult": {
"changes": {
"identifier.js": [
"Deleted the 'theVar2' identifier",
"Deleted the 'theVar' identifier",
"Added the 'theVar2' identifier"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'theVar2' identifier"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'theVar' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
8
]
}
},
"summary": "Added the 'theVar2' identifier"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"identifier.js"
],
"sha1": "43486e90c660f961f930e3e22143865875bcd5ff",
"sha1": "cfb79cbb2bcd620edb55c909983e5e631a08c863",
"gitDir": "test/corpus/repos/javascript",
"sha2": "dad7ef451c5c151221fdd249d81634c437ebd8d7"
"sha2": "106dff12bfb07dc175748db3ce6f8a6ace4a561a"
}
,{
"testCaseDescription": "javascript-identifier-delete-test",
"expectedResult": {
"changes": {
"identifier.js": [
"Deleted the 'theVar' identifier"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'theVar' identifier"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"identifier.js"
],
"sha1": "dad7ef451c5c151221fdd249d81634c437ebd8d7",
"sha1": "106dff12bfb07dc175748db3ce6f8a6ace4a561a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2c5321229447560cf390e01286dc9b30cfdefe51"
"sha2": "947a90cdedee234b01c85052f7bb112fb1e7eae0"
}
,{
"testCaseDescription": "javascript-identifier-delete-rest-test",
"expectedResult": {
"changes": {
"identifier.js": [
"Deleted the 'theVar2' identifier"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'theVar2' identifier"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"identifier.js"
],
"sha1": "2c5321229447560cf390e01286dc9b30cfdefe51",
"sha1": "947a90cdedee234b01c85052f7bb112fb1e7eae0",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d04271adf62b579bffb014a03e4e401ce79164ea"
"sha2": "d7c66b2feea9aa25c92f9e3005737bcd96679136"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"if-else.js": [
"Added the 'x' if statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
25
]
}
},
"summary": "Added the 'x' if statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"if-else.js"
],
"sha1": "29f1d26b0bc64aa6be6229eca7f4367b07aa1170",
"sha1": "177b3db7ca070dc750876553a0cd7fde8b5df54c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "da3afa1c9c1d613c1d97a8742b9988e9c8339d8a"
"sha2": "fd499e58d749df1da475f0d6033825f265734210"
}
,{
"testCaseDescription": "javascript-if-else-replacement-insert-test",
"expectedResult": {
"changes": {
"if-else.js": [
"Added the 'a' if statement",
"Added the 'x' if statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
29
]
}
},
"summary": "Added the 'a' if statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
25
]
}
},
"summary": "Added the 'x' if statement"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"if-else.js"
],
"sha1": "da3afa1c9c1d613c1d97a8742b9988e9c8339d8a",
"sha1": "fd499e58d749df1da475f0d6033825f265734210",
"gitDir": "test/corpus/repos/javascript",
"sha2": "bfadcfba5d33447609b3379e692de640b9c1cd65"
"sha2": "1f6c19a2b78ca415ac6e06f69c051ba6c23a250e"
}
,{
"testCaseDescription": "javascript-if-else-delete-insert-test",
"expectedResult": {
"changes": {
"if-else.js": [
"Replaced the 'a' if statement with the 'x' if statement"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
29
]
},
{
"start": [
1,
1
],
"end": [
1,
25
]
}
]
},
"summary": "Replaced the 'a' if statement with the 'x' if statement"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"if-else.js"
],
"sha1": "bfadcfba5d33447609b3379e692de640b9c1cd65",
"sha1": "1f6c19a2b78ca415ac6e06f69c051ba6c23a250e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7abc67596365fc0013d57b7dc5d2a3388adea07a"
"sha2": "946c2d3269de0a2f284a9922b8da111323729827"
}
,{
"testCaseDescription": "javascript-if-else-replacement-test",
"expectedResult": {
"changes": {
"if-else.js": [
"Replaced the 'x' if statement with the 'a' if statement"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
25
]
},
{
"start": [
1,
1
],
"end": [
1,
29
]
}
]
},
"summary": "Replaced the 'x' if statement with the 'a' if statement"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"if-else.js"
],
"sha1": "7abc67596365fc0013d57b7dc5d2a3388adea07a",
"sha1": "946c2d3269de0a2f284a9922b8da111323729827",
"gitDir": "test/corpus/repos/javascript",
"sha2": "caf0ea14c8bd9cbe27ba7ec96b17c277975ccf12"
"sha2": "71792b4ff0291e41c9e3ec3157abfea9cd67daa7"
}
,{
"testCaseDescription": "javascript-if-else-delete-replacement-test",
"expectedResult": {
"changes": {
"if-else.js": [
"Deleted the 'a' if statement",
"Deleted the 'x' if statement",
"Added the 'a' if statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
29
]
}
},
"summary": "Deleted the 'a' if statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
25
]
}
},
"summary": "Deleted the 'x' if statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
29
]
}
},
"summary": "Added the 'a' if statement"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"if-else.js"
],
"sha1": "caf0ea14c8bd9cbe27ba7ec96b17c277975ccf12",
"sha1": "71792b4ff0291e41c9e3ec3157abfea9cd67daa7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "468dba9f1e10be8103b23d5e62b8e5eb5ec248b4"
"sha2": "95edd1d597a111bbe508c047a0f75d0342b35cea"
}
,{
"testCaseDescription": "javascript-if-else-delete-test",
"expectedResult": {
"changes": {
"if-else.js": [
"Deleted the 'x' if statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
25
]
}
},
"summary": "Deleted the 'x' if statement"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"if-else.js"
],
"sha1": "468dba9f1e10be8103b23d5e62b8e5eb5ec248b4",
"sha1": "95edd1d597a111bbe508c047a0f75d0342b35cea",
"gitDir": "test/corpus/repos/javascript",
"sha2": "fbd6b6699f53911ee07f065488e36166f0cc5d30"
"sha2": "58fd81ed8b29ab258997ccdcb2a0602e64748fc8"
}
,{
"testCaseDescription": "javascript-if-else-delete-rest-test",
"expectedResult": {
"changes": {
"if-else.js": [
"Deleted the 'a' if statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
29
]
}
},
"summary": "Deleted the 'a' if statement"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"if-else.js"
],
"sha1": "fbd6b6699f53911ee07f065488e36166f0cc5d30",
"sha1": "58fd81ed8b29ab258997ccdcb2a0602e64748fc8",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2177649d1d22edbb1ab004346f327e906b362e8d"
"sha2": "73e8a48299a8c408fadbf83077ab1e56ea81b5b0"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"if.js": [
"Added the 'x' if statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
19
]
}
},
"summary": "Added the 'x' if statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"if.js"
],
"sha1": "57c773af116921575b844893c03a256cc1464667",
"sha1": "12025ea457b9f71f1c34d8354dcfef593fccd770",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9a036a1ba7629580a3a26267e39c063bac430795"
"sha2": "be1ba1d9246e11b23be78baf2717476ab716b9bf"
}
,{
"testCaseDescription": "javascript-if-replacement-insert-test",
"expectedResult": {
"changes": {
"if.js": [
"Added the 'a.b' if statement",
"Added the 'x' if statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
24
]
}
},
"summary": "Added the 'a.b' if statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Added the 'x' if statement"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"if.js"
],
"sha1": "9a036a1ba7629580a3a26267e39c063bac430795",
"sha1": "be1ba1d9246e11b23be78baf2717476ab716b9bf",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7c9866e86d569085e701e86e5d4b6eb93d5a6b62"
"sha2": "c01e982383545a2a238b3a6af70f2c1268e473d6"
}
,{
"testCaseDescription": "javascript-if-delete-insert-test",
"expectedResult": {
"changes": {
"if.js": [
"Replaced the 'a.b' if statement with the 'x' if statement"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
24
]
},
{
"start": [
1,
1
],
"end": [
1,
19
]
}
]
},
"summary": "Replaced the 'a.b' if statement with the 'x' if statement"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"if.js"
],
"sha1": "7c9866e86d569085e701e86e5d4b6eb93d5a6b62",
"sha1": "c01e982383545a2a238b3a6af70f2c1268e473d6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "c26f374cd4c53ae211a4e027e0e162563d16cbcb"
"sha2": "6040b05311f729269cebedf1d54c8038788faf89"
}
,{
"testCaseDescription": "javascript-if-replacement-test",
"expectedResult": {
"changes": {
"if.js": [
"Replaced the 'x' if statement with the 'a.b' if statement"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
19
]
},
{
"start": [
1,
1
],
"end": [
1,
24
]
}
]
},
"summary": "Replaced the 'x' if statement with the 'a.b' if statement"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"if.js"
],
"sha1": "c26f374cd4c53ae211a4e027e0e162563d16cbcb",
"sha1": "6040b05311f729269cebedf1d54c8038788faf89",
"gitDir": "test/corpus/repos/javascript",
"sha2": "812ef983ac5d4f52dce7f22284a3cfbe0799dc08"
"sha2": "ea9839117fdd5a20b5a49fd5bec5b0edf373e914"
}
,{
"testCaseDescription": "javascript-if-delete-replacement-test",
"expectedResult": {
"changes": {
"if.js": [
"Deleted the 'a.b' if statement",
"Deleted the 'x' if statement",
"Added the 'a.b' if statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
24
]
}
},
"summary": "Deleted the 'a.b' if statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Deleted the 'x' if statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
24
]
}
},
"summary": "Added the 'a.b' if statement"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"if.js"
],
"sha1": "812ef983ac5d4f52dce7f22284a3cfbe0799dc08",
"sha1": "ea9839117fdd5a20b5a49fd5bec5b0edf373e914",
"gitDir": "test/corpus/repos/javascript",
"sha2": "68ef64a63db680b54e82ce764af5df50a20fd90d"
"sha2": "450d9d28a46d3283979a55c31dcf4cd7fadd979b"
}
,{
"testCaseDescription": "javascript-if-delete-test",
"expectedResult": {
"changes": {
"if.js": [
"Deleted the 'x' if statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
19
]
}
},
"summary": "Deleted the 'x' if statement"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"if.js"
],
"sha1": "68ef64a63db680b54e82ce764af5df50a20fd90d",
"sha1": "450d9d28a46d3283979a55c31dcf4cd7fadd979b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "028cd8f2800eb41fd83b1d55eaa3ad0b993c31a3"
"sha2": "d96611306db475c3b49c4e6f7c2ac07fedee9c42"
}
,{
"testCaseDescription": "javascript-if-delete-rest-test",
"expectedResult": {
"changes": {
"if.js": [
"Deleted the 'a.b' if statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
24
]
}
},
"summary": "Deleted the 'a.b' if statement"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"if.js"
],
"sha1": "028cd8f2800eb41fd83b1d55eaa3ad0b993c31a3",
"sha1": "d96611306db475c3b49c4e6f7c2ac07fedee9c42",
"gitDir": "test/corpus/repos/javascript",
"sha2": "29f1d26b0bc64aa6be6229eca7f4367b07aa1170"
"sha2": "0e12557e9a116aa82c320e964f67655fe82a8476"
}]

File diff suppressed because it is too large Load Diff

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"math-assignment-operator.js": [
"Added the 'x' math assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Added the 'x' math assignment"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"math-assignment-operator.js"
],
"sha1": "70a57d3ee8bb0f31663af70c592c7e294522a194",
"sha1": "20c9fcd2968854089edd9800a50d5c4a92d8e07b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "587e39b227f49afbbd8734d70873c2204ff20707"
"sha2": "44a0ac752ed04f0db713416a4b71465fcb6791e5"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-replacement-insert-test",
"expectedResult": {
"changes": {
"math-assignment-operator.js": [
"Added the 'x' math assignment",
"Added the 'x' math assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Added the 'x' math assignment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Added the 'x' math assignment"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"math-assignment-operator.js"
],
"sha1": "587e39b227f49afbbd8734d70873c2204ff20707",
"sha1": "44a0ac752ed04f0db713416a4b71465fcb6791e5",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5895e0e380c0419193d04010cca1784eeba15916"
"sha2": "9186895045b5796889b609b6804f3ca92d100c37"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-insert-test",
"expectedResult": {
"changes": {
"math-assignment-operator.js": [
"Replaced '2' with '1' in the x math assignment"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
7
]
},
{
"start": [
1,
6
],
"end": [
1,
7
]
}
]
},
"summary": "Replaced '2' with '1' in the x math assignment"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"math-assignment-operator.js"
],
"sha1": "5895e0e380c0419193d04010cca1784eeba15916",
"sha1": "9186895045b5796889b609b6804f3ca92d100c37",
"gitDir": "test/corpus/repos/javascript",
"sha2": "560d079678ad8723705a343ec6ff3c6d7fa1de52"
"sha2": "708ef787fa29646989c2a62e3a38224c6e54150a"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-replacement-test",
"expectedResult": {
"changes": {
"math-assignment-operator.js": [
"Replaced '1' with '2' in the x math assignment"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
7
]
},
{
"start": [
1,
6
],
"end": [
1,
7
]
}
]
},
"summary": "Replaced '1' with '2' in the x math assignment"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"math-assignment-operator.js"
],
"sha1": "560d079678ad8723705a343ec6ff3c6d7fa1de52",
"sha1": "708ef787fa29646989c2a62e3a38224c6e54150a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9b88562e4d8ae59d124ae4fbb3497e23df0ac59f"
"sha2": "dba9d03bc3f05c75c64261dc7980015b55215097"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-replacement-test",
"expectedResult": {
"changes": {
"math-assignment-operator.js": [
"Deleted the 'x' math assignment",
"Deleted the 'x' math assignment",
"Added the 'x' math assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'x' math assignment"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'x' math assignment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Added the 'x' math assignment"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"math-assignment-operator.js"
],
"sha1": "9b88562e4d8ae59d124ae4fbb3497e23df0ac59f",
"sha1": "dba9d03bc3f05c75c64261dc7980015b55215097",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d31232ad00dc03a03313602332a890bf729aab26"
"sha2": "4b9bb90264994d44abe5f4178554cbc9364b3fac"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-test",
"expectedResult": {
"changes": {
"math-assignment-operator.js": [
"Deleted the 'x' math assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'x' math assignment"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"math-assignment-operator.js"
],
"sha1": "d31232ad00dc03a03313602332a890bf729aab26",
"sha1": "4b9bb90264994d44abe5f4178554cbc9364b3fac",
"gitDir": "test/corpus/repos/javascript",
"sha2": "918b9d9b380f111754955445b1610ca37847cbc4"
"sha2": "c6ca546f3e99646514f92e89805309dc8ee3a519"
}
,{
"testCaseDescription": "javascript-math-assignment-operator-delete-rest-test",
"expectedResult": {
"changes": {
"math-assignment-operator.js": [
"Deleted the 'x' math assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'x' math assignment"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"math-assignment-operator.js"
],
"sha1": "918b9d9b380f111754955445b1610ca37847cbc4",
"sha1": "c6ca546f3e99646514f92e89805309dc8ee3a519",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b2a12ed6ee90000f320e8bd5b90383e28e847abb"
"sha2": "296397df0f0e65c6e8ab7e4962469076b890cd66"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"math-operator.js": [
"Added the 'i + j * 3 - j % 5' math operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Added the 'i + j * 3 - j % 5' math operator"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"math-operator.js"
],
"sha1": "791e48fc86effe144352469c272e5d429d114edc",
"sha1": "94851cf65efff14a5d6caad6c5ec3055d75f6891",
"gitDir": "test/corpus/repos/javascript",
"sha2": "12d9fd481eb702ad9c6cb4833a43de12a6d3623b"
"sha2": "5154551d7bb3028e34b78c57ef6e8251941c5e24"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Added the 'i + j * 2 - j % 4' math operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
18
]
}
},
"summary": "Added the 'i + j * 3 - j % 5' math operator"
}
]
},
"errors": {}
@ -29,17 +71,69 @@
"filePaths": [
"math-operator.js"
],
"sha1": "12d9fd481eb702ad9c6cb4833a43de12a6d3623b",
"sha1": "5154551d7bb3028e34b78c57ef6e8251941c5e24",
"gitDir": "test/corpus/repos/javascript",
"sha2": "73d01982b75b34d4ba3c4cbf05222dabecab8ae5"
"sha2": "fc5286a2ab8fbc26558fc824e1673af4c9444af0"
}
,{
"testCaseDescription": "javascript-math-operator-delete-insert-test",
"expectedResult": {
"changes": {
"math-operator.js": [
"Replaced '2' with '3'",
"Replaced '4' with '5'"
{
"span": {
"replace": [
{
"start": [
1,
9
],
"end": [
1,
10
]
},
{
"start": [
1,
9
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced '2' with '3'"
},
{
"span": {
"replace": [
{
"start": [
1,
17
],
"end": [
1,
18
]
},
{
"start": [
1,
17
],
"end": [
1,
18
]
}
]
},
"summary": "Replaced '4' with '5'"
}
]
},
"errors": {}
@ -47,17 +141,69 @@
"filePaths": [
"math-operator.js"
],
"sha1": "73d01982b75b34d4ba3c4cbf05222dabecab8ae5",
"sha1": "fc5286a2ab8fbc26558fc824e1673af4c9444af0",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5dd11323300319a5f427c6c00e247581f4746a49"
"sha2": "20ff08f05738054ae97a55afe187f062018e7b4a"
}
,{
"testCaseDescription": "javascript-math-operator-replacement-test",
"expectedResult": {
"changes": {
"math-operator.js": [
"Replaced '3' with '2'",
"Replaced '5' with '4'"
{
"span": {
"replace": [
{
"start": [
1,
9
],
"end": [
1,
10
]
},
{
"start": [
1,
9
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced '3' with '2'"
},
{
"span": {
"replace": [
{
"start": [
1,
17
],
"end": [
1,
18
]
},
{
"start": [
1,
17
],
"end": [
1,
18
]
}
]
},
"summary": "Replaced '5' with '4'"
}
]
},
"errors": {}
@ -65,18 +211,60 @@
"filePaths": [
"math-operator.js"
],
"sha1": "5dd11323300319a5f427c6c00e247581f4746a49",
"sha1": "20ff08f05738054ae97a55afe187f062018e7b4a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e3b8421ee2cfb62d013aaca89aae5383d595d3f6"
"sha2": "b633411825d8d0d6e48285da3ac8a127bb5b833f"
}
,{
"testCaseDescription": "javascript-math-operator-delete-replacement-test",
"expectedResult": {
"changes": {
"math-operator.js": [
"Deleted the 'i + j * 2 - j % 4' math operator",
"Deleted the 'i + j * 3 - j % 5' math operator",
"Added the 'i + j * 2 - j % 4' math operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the 'i + j * 2 - j % 4' math operator"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
18
]
}
},
"summary": "Deleted the 'i + j * 3 - j % 5' math operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
18
]
}
},
"summary": "Added the 'i + j * 2 - j % 4' math operator"
}
]
},
"errors": {}
@ -84,16 +272,30 @@
"filePaths": [
"math-operator.js"
],
"sha1": "e3b8421ee2cfb62d013aaca89aae5383d595d3f6",
"sha1": "b633411825d8d0d6e48285da3ac8a127bb5b833f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ad9c3f6ff657950f129f7ef99a807877ca57b3e6"
"sha2": "5fba7f8da7725787273fb9fdff3650ee0572bfcd"
}
,{
"testCaseDescription": "javascript-math-operator-delete-test",
"expectedResult": {
"changes": {
"math-operator.js": [
"Deleted the 'i + j * 3 - j % 5' math operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the 'i + j * 3 - j % 5' math operator"
}
]
},
"errors": {}
@ -101,16 +303,30 @@
"filePaths": [
"math-operator.js"
],
"sha1": "ad9c3f6ff657950f129f7ef99a807877ca57b3e6",
"sha1": "5fba7f8da7725787273fb9fdff3650ee0572bfcd",
"gitDir": "test/corpus/repos/javascript",
"sha2": "05bc5db6db458b9b9b82238fd3c054439b4ec380"
"sha2": "971b37d42e25cdfa61a5023a7fbbef5321f2848a"
}
,{
"testCaseDescription": "javascript-math-operator-delete-rest-test",
"expectedResult": {
"changes": {
"math-operator.js": [
"Deleted the 'i + j * 2 - j % 4' math operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the 'i + j * 2 - j % 4' math operator"
}
]
},
"errors": {}
@ -118,7 +334,7 @@
"filePaths": [
"math-operator.js"
],
"sha1": "05bc5db6db458b9b9b82238fd3c054439b4ec380",
"sha1": "971b37d42e25cdfa61a5023a7fbbef5321f2848a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5e4697c7ee184c7dfdecd9059fc2c5058131cf05"
"sha2": "86115e374d32bc9d7b6c8dd347d7ec900b501880"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"member-access-assignment.js": [
"Added the 'y.x' assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Added the 'y.x' assignment"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"member-access-assignment.js"
],
"sha1": "36cf72c8436b4fcab0a1f6f85b659b979af0a331",
"sha1": "372f806f1ac14eeaef4f8dd5ae1f081823efe483",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d87821cc15d36a738643a185d75ee4801ba1458b"
"sha2": "a1055cc31a158a5fa654aa40427592b3d6b10c88"
}
,{
"testCaseDescription": "javascript-member-access-assignment-replacement-insert-test",
"expectedResult": {
"changes": {
"member-access-assignment.js": [
"Added the 'y.x' assignment",
"Added the 'y.x' assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Added the 'y.x' assignment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
8
]
}
},
"summary": "Added the 'y.x' assignment"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"member-access-assignment.js"
],
"sha1": "d87821cc15d36a738643a185d75ee4801ba1458b",
"sha1": "a1055cc31a158a5fa654aa40427592b3d6b10c88",
"gitDir": "test/corpus/repos/javascript",
"sha2": "75b310b64e8a439d13af9e2e4a593c954738209d"
"sha2": "639b924cdb7df8d54c5accd88915cc8843556868"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-insert-test",
"expectedResult": {
"changes": {
"member-access-assignment.js": [
"Replaced '1' with '0' in an assignment to y.x"
{
"span": {
"replace": [
{
"start": [
1,
7
],
"end": [
1,
8
]
},
{
"start": [
1,
7
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced '1' with '0' in an assignment to y.x"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"member-access-assignment.js"
],
"sha1": "75b310b64e8a439d13af9e2e4a593c954738209d",
"sha1": "639b924cdb7df8d54c5accd88915cc8843556868",
"gitDir": "test/corpus/repos/javascript",
"sha2": "cdb0ea086b19919dbcf6b92f19b8c4c11924d3ad"
"sha2": "21f1f660aaa494d71f21feebf996dee749004e74"
}
,{
"testCaseDescription": "javascript-member-access-assignment-replacement-test",
"expectedResult": {
"changes": {
"member-access-assignment.js": [
"Replaced '0' with '1' in an assignment to y.x"
{
"span": {
"replace": [
{
"start": [
1,
7
],
"end": [
1,
8
]
},
{
"start": [
1,
7
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced '0' with '1' in an assignment to y.x"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"member-access-assignment.js"
],
"sha1": "cdb0ea086b19919dbcf6b92f19b8c4c11924d3ad",
"sha1": "21f1f660aaa494d71f21feebf996dee749004e74",
"gitDir": "test/corpus/repos/javascript",
"sha2": "c8cd3670bf4acb97bd411fe9ab3431377e8fe2a7"
"sha2": "62c47a061654573bb752aae3bd9ef9bcceaddf20"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-replacement-test",
"expectedResult": {
"changes": {
"member-access-assignment.js": [
"Deleted the 'y.x' assignment",
"Deleted the 'y.x' assignment",
"Added the 'y.x' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'y.x' assignment"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
8
]
}
},
"summary": "Deleted the 'y.x' assignment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
8
]
}
},
"summary": "Added the 'y.x' assignment"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"member-access-assignment.js"
],
"sha1": "c8cd3670bf4acb97bd411fe9ab3431377e8fe2a7",
"sha1": "62c47a061654573bb752aae3bd9ef9bcceaddf20",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e76071835624b33a7fb5bf1f9ab7dfcab10e9b3d"
"sha2": "19c82c7fd6b8e019cf970ad495af8c0998610f6f"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-test",
"expectedResult": {
"changes": {
"member-access-assignment.js": [
"Deleted the 'y.x' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'y.x' assignment"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"member-access-assignment.js"
],
"sha1": "e76071835624b33a7fb5bf1f9ab7dfcab10e9b3d",
"sha1": "19c82c7fd6b8e019cf970ad495af8c0998610f6f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "fa75ab164595aadae5250d237f1aac21ba453b4b"
"sha2": "c87076b2cfb63f72f222f023fe8aa0d28927632a"
}
,{
"testCaseDescription": "javascript-member-access-assignment-delete-rest-test",
"expectedResult": {
"changes": {
"member-access-assignment.js": [
"Deleted the 'y.x' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'y.x' assignment"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"member-access-assignment.js"
],
"sha1": "fa75ab164595aadae5250d237f1aac21ba453b4b",
"sha1": "c87076b2cfb63f72f222f023fe8aa0d28927632a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "63243f11ee238a04b1c51987a7cbc7d48f5f405b"
"sha2": "9ca89bc6c9066b34bc18aecce4f646208c65c907"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"member-access.js": [
"Added the 'x.someProperty' member access"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
15
]
}
},
"summary": "Added the 'x.someProperty' member access"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"member-access.js"
],
"sha1": "733ae2c2622361c892fe98fdad05f30f654595e3",
"sha1": "8c89ac29c02f4714dc946e2824152d320b623e36",
"gitDir": "test/corpus/repos/javascript",
"sha2": "1c89ad3de46a5bb26df57ab96925c29c360a7a81"
"sha2": "7819fe045b5f19ee470b8f0d2371d9344f6c183a"
}
,{
"testCaseDescription": "javascript-member-access-replacement-insert-test",
"expectedResult": {
"changes": {
"member-access.js": [
"Added the 'x.someOtherProperty' member access",
"Added the 'x.someProperty' member access"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Added the 'x.someOtherProperty' member access"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
15
]
}
},
"summary": "Added the 'x.someProperty' member access"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"member-access.js"
],
"sha1": "1c89ad3de46a5bb26df57ab96925c29c360a7a81",
"sha1": "7819fe045b5f19ee470b8f0d2371d9344f6c183a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "33bef6695810d90e7b41be5198a9384691573d95"
"sha2": "823d52271b2d99c48216948e20cec0ba6b9d1e6e"
}
,{
"testCaseDescription": "javascript-member-access-delete-insert-test",
"expectedResult": {
"changes": {
"member-access.js": [
"Replaced the 'someOtherProperty' identifier with the 'someProperty' identifier"
{
"span": {
"replace": [
{
"start": [
1,
3
],
"end": [
1,
20
]
},
{
"start": [
1,
3
],
"end": [
1,
15
]
}
]
},
"summary": "Replaced the 'someOtherProperty' identifier with the 'someProperty' identifier"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"member-access.js"
],
"sha1": "33bef6695810d90e7b41be5198a9384691573d95",
"sha1": "823d52271b2d99c48216948e20cec0ba6b9d1e6e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ee62b57b7a897b3bae85dbd988a5c817c92c0697"
"sha2": "dd0030c04fcaf1e5784706aee9760bd9904495b8"
}
,{
"testCaseDescription": "javascript-member-access-replacement-test",
"expectedResult": {
"changes": {
"member-access.js": [
"Replaced the 'someProperty' identifier with the 'someOtherProperty' identifier"
{
"span": {
"replace": [
{
"start": [
1,
3
],
"end": [
1,
15
]
},
{
"start": [
1,
3
],
"end": [
1,
20
]
}
]
},
"summary": "Replaced the 'someProperty' identifier with the 'someOtherProperty' identifier"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"member-access.js"
],
"sha1": "ee62b57b7a897b3bae85dbd988a5c817c92c0697",
"sha1": "dd0030c04fcaf1e5784706aee9760bd9904495b8",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e1853a7ecd687ec0eb3e215ad304f9dc65734f4d"
"sha2": "88e2ad3ffa0cca807aeb6e2ea97562c04034a954"
}
,{
"testCaseDescription": "javascript-member-access-delete-replacement-test",
"expectedResult": {
"changes": {
"member-access.js": [
"Deleted the 'x.someOtherProperty' member access",
"Deleted the 'x.someProperty' member access",
"Added the 'x.someOtherProperty' member access"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Deleted the 'x.someOtherProperty' member access"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
15
]
}
},
"summary": "Deleted the 'x.someProperty' member access"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
20
]
}
},
"summary": "Added the 'x.someOtherProperty' member access"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"member-access.js"
],
"sha1": "e1853a7ecd687ec0eb3e215ad304f9dc65734f4d",
"sha1": "88e2ad3ffa0cca807aeb6e2ea97562c04034a954",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b8c73295541ffbad48aaeba23037596710909140"
"sha2": "2aaeaae2047b4dea6cb7f6a0851e0314b682b856"
}
,{
"testCaseDescription": "javascript-member-access-delete-test",
"expectedResult": {
"changes": {
"member-access.js": [
"Deleted the 'x.someProperty' member access"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
15
]
}
},
"summary": "Deleted the 'x.someProperty' member access"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"member-access.js"
],
"sha1": "b8c73295541ffbad48aaeba23037596710909140",
"sha1": "2aaeaae2047b4dea6cb7f6a0851e0314b682b856",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f3ff0af2070ffb4d4383ea4eea53b92c7abd0030"
"sha2": "5ee7c25fc11122ae36f4a585fafbe0d0f69ed1b9"
}
,{
"testCaseDescription": "javascript-member-access-delete-rest-test",
"expectedResult": {
"changes": {
"member-access.js": [
"Deleted the 'x.someOtherProperty' member access"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Deleted the 'x.someOtherProperty' member access"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"member-access.js"
],
"sha1": "f3ff0af2070ffb4d4383ea4eea53b92c7abd0030",
"sha1": "5ee7c25fc11122ae36f4a585fafbe0d0f69ed1b9",
"gitDir": "test/corpus/repos/javascript",
"sha2": "39134301fe3c61d2958c5cd1e72bc40a4945825b"
"sha2": "b5aeb51a21b78d1547cc65d09bad74c4e27f68c6"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"method-call.js": [
"Added the 'object.someMethod(arg1, \"arg2\")' method call"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"method-call.js"
],
"sha1": "5e933ecc7f1454b396bd04022556601bcf8de7ab",
"sha1": "a37267842ee6f1e161c4316af0cb35f4b632a059",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d5c49b4be18c2ab655996bdd3a91482e9fc3ce9c"
"sha2": "609913d4f6d79ee00e3d411b2e3915071ad635f5"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
32
]
}
},
"summary": "Added the 'object.someMethod(arg1, \"arg2\")' method call"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"method-call.js"
],
"sha1": "d5c49b4be18c2ab655996bdd3a91482e9fc3ce9c",
"sha1": "609913d4f6d79ee00e3d411b2e3915071ad635f5",
"gitDir": "test/corpus/repos/javascript",
"sha2": "cb91783ae43cb3c50e645b8631425987562fa9b3"
"sha2": "33a0c4183dd058b371cce8b43c01dc788edd30f2"
}
,{
"testCaseDescription": "javascript-method-call-delete-insert-test",
"expectedResult": {
"changes": {
"method-call.js": [
"Replaced the \"arg3\" string with the \"arg2\" string in the object.someMethod(arg1, \"arg2\") method call"
{
"span": {
"replace": [
{
"start": [
1,
25
],
"end": [
1,
31
]
},
{
"start": [
1,
25
],
"end": [
1,
31
]
}
]
},
"summary": "Replaced the \"arg3\" string with the \"arg2\" string in the object.someMethod(arg1, \"arg2\") method call"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"method-call.js"
],
"sha1": "cb91783ae43cb3c50e645b8631425987562fa9b3",
"sha1": "33a0c4183dd058b371cce8b43c01dc788edd30f2",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4213cac18eed39c24d1538ad8c3967e08cb4c4ad"
"sha2": "b350dc1500aa52926e6cd6fedc4e04375a2f3828"
}
,{
"testCaseDescription": "javascript-method-call-replacement-test",
"expectedResult": {
"changes": {
"method-call.js": [
"Replaced the \"arg2\" string with the \"arg3\" string in the object.someMethod(arg1, \"arg3\") method call"
{
"span": {
"replace": [
{
"start": [
1,
25
],
"end": [
1,
31
]
},
{
"start": [
1,
25
],
"end": [
1,
31
]
}
]
},
"summary": "Replaced the \"arg2\" string with the \"arg3\" string in the object.someMethod(arg1, \"arg3\") method call"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"method-call.js"
],
"sha1": "4213cac18eed39c24d1538ad8c3967e08cb4c4ad",
"sha1": "b350dc1500aa52926e6cd6fedc4e04375a2f3828",
"gitDir": "test/corpus/repos/javascript",
"sha2": "96cd5a62c827403f9fd682d8b00b91d691a6a9cc"
"sha2": "ee87a9ae5d5c4a2518eb5f7ef0b26bd9b0a371e6"
}
,{
"testCaseDescription": "javascript-method-call-delete-replacement-test",
"expectedResult": {
"changes": {
"method-call.js": [
"Deleted the 'object.someMethod(arg1, \"arg3\")' method call",
"Deleted the 'object.someMethod(arg1, \"arg2\")' method call",
"Added the 'object.someMethod(arg1, \"arg3\")' method call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
32
]
}
},
"summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
32
]
}
},
"summary": "Added the 'object.someMethod(arg1, \"arg3\")' method call"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"method-call.js"
],
"sha1": "96cd5a62c827403f9fd682d8b00b91d691a6a9cc",
"sha1": "ee87a9ae5d5c4a2518eb5f7ef0b26bd9b0a371e6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2569aa3a97089f93caf1992871b5e4f3573b0877"
"sha2": "794adc95ac0d89beca54fc417b94eaf5ac50ec58"
}
,{
"testCaseDescription": "javascript-method-call-delete-test",
"expectedResult": {
"changes": {
"method-call.js": [
"Deleted the 'object.someMethod(arg1, \"arg2\")' method call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Deleted the 'object.someMethod(arg1, \"arg2\")' method call"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"method-call.js"
],
"sha1": "2569aa3a97089f93caf1992871b5e4f3573b0877",
"sha1": "794adc95ac0d89beca54fc417b94eaf5ac50ec58",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ed2ca022ea846444da59fa55719ca5d5e54cc047"
"sha2": "db28776718addccb53343bee695b484d8a389784"
}
,{
"testCaseDescription": "javascript-method-call-delete-rest-test",
"expectedResult": {
"changes": {
"method-call.js": [
"Deleted the 'object.someMethod(arg1, \"arg3\")' method call"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Deleted the 'object.someMethod(arg1, \"arg3\")' method call"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"method-call.js"
],
"sha1": "ed2ca022ea846444da59fa55719ca5d5e54cc047",
"sha1": "db28776718addccb53343bee695b484d8a389784",
"gitDir": "test/corpus/repos/javascript",
"sha2": "53a9c959778b42d9f34bfc266d177a6f1b3065fd"
"sha2": "7b45d5b720f557df4fbd880be8c0e292c4defdc4"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"named-function.js": [
"Added the 'myFunction' function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
42
]
}
},
"summary": "Added the 'myFunction' function"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"named-function.js"
],
"sha1": "12ad7dc9f0bac8d9da1560cc4e1b965b0a04f159",
"sha1": "caeacf57ee751440e4f9b9f606df460c17499bdd",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a5b5b152ae974c6ce11496a26feaa61a00c029de"
"sha2": "742ee12fc034748905977d3e1ba7818df34b9b66"
}
,{
"testCaseDescription": "javascript-named-function-replacement-insert-test",
"expectedResult": {
"changes": {
"named-function.js": [
"Added the 'anotherFunction' function",
"Added the 'myFunction' function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
45
]
}
},
"summary": "Added the 'anotherFunction' function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
42
]
}
},
"summary": "Added the 'myFunction' function"
}
]
},
"errors": {}
@ -29,20 +71,102 @@
"filePaths": [
"named-function.js"
],
"sha1": "a5b5b152ae974c6ce11496a26feaa61a00c029de",
"sha1": "742ee12fc034748905977d3e1ba7818df34b9b66",
"gitDir": "test/corpus/repos/javascript",
"sha2": "420b207c8f28d5fcc46792a61821cc1be3908c4e"
"sha2": "05f7b98428d31fa7ae97f65b6c901b8b392764f7"
}
,{
"testCaseDescription": "javascript-named-function-delete-insert-test",
"expectedResult": {
"changes": {
"named-function.js": [
"Replaced the 'anotherFunction' identifier with the 'myFunction' identifier in the myFunction function",
"Added the 'arg1' identifier in the myFunction function",
"Added the 'arg2' identifier in the myFunction function",
"Added the 'arg2' identifier in the myFunction function",
"Deleted the 'false' return statement in the myFunction function"
{
"span": {
"replace": [
{
"start": [
1,
10
],
"end": [
1,
25
]
},
{
"start": [
1,
10
],
"end": [
1,
20
]
}
]
},
"summary": "Replaced the 'anotherFunction' identifier with the 'myFunction' identifier in the myFunction function"
},
{
"span": {
"insert": {
"start": [
1,
21
],
"end": [
1,
25
]
}
},
"summary": "Added the 'arg1' identifier in the myFunction function"
},
{
"span": {
"insert": {
"start": [
1,
27
],
"end": [
1,
31
]
}
},
"summary": "Added the 'arg2' identifier in the myFunction function"
},
{
"span": {
"insert": {
"start": [
1,
35
],
"end": [
1,
39
]
}
},
"summary": "Added the 'arg2' identifier in the myFunction function"
},
{
"span": {
"delete": {
"start": [
1,
30
],
"end": [
1,
43
]
}
},
"summary": "Deleted the 'false' return statement in the myFunction function"
}
]
},
"errors": {}
@ -50,20 +174,102 @@
"filePaths": [
"named-function.js"
],
"sha1": "420b207c8f28d5fcc46792a61821cc1be3908c4e",
"sha1": "05f7b98428d31fa7ae97f65b6c901b8b392764f7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "040f725b6a703695bdbccd0122445aee920b078e"
"sha2": "e60e4118dca7f21ef5d06d668e6f6961f94ece60"
}
,{
"testCaseDescription": "javascript-named-function-replacement-test",
"expectedResult": {
"changes": {
"named-function.js": [
"Replaced the 'myFunction' identifier with the 'anotherFunction' identifier in the anotherFunction function",
"Deleted the 'arg1' identifier in the anotherFunction function",
"Deleted the 'arg2' identifier in the anotherFunction function",
"Added the 'false' return statement in the anotherFunction function",
"Deleted the 'arg2' identifier in the anotherFunction function"
{
"span": {
"replace": [
{
"start": [
1,
10
],
"end": [
1,
20
]
},
{
"start": [
1,
10
],
"end": [
1,
25
]
}
]
},
"summary": "Replaced the 'myFunction' identifier with the 'anotherFunction' identifier in the anotherFunction function"
},
{
"span": {
"delete": {
"start": [
1,
21
],
"end": [
1,
25
]
}
},
"summary": "Deleted the 'arg1' identifier in the anotherFunction function"
},
{
"span": {
"delete": {
"start": [
1,
27
],
"end": [
1,
31
]
}
},
"summary": "Deleted the 'arg2' identifier in the anotherFunction function"
},
{
"span": {
"insert": {
"start": [
1,
30
],
"end": [
1,
43
]
}
},
"summary": "Added the 'false' return statement in the anotherFunction function"
},
{
"span": {
"delete": {
"start": [
1,
35
],
"end": [
1,
39
]
}
},
"summary": "Deleted the 'arg2' identifier in the anotherFunction function"
}
]
},
"errors": {}
@ -71,18 +277,60 @@
"filePaths": [
"named-function.js"
],
"sha1": "040f725b6a703695bdbccd0122445aee920b078e",
"sha1": "e60e4118dca7f21ef5d06d668e6f6961f94ece60",
"gitDir": "test/corpus/repos/javascript",
"sha2": "061e26b3f1bf6b9e8ee101e8dbbf1e0b24796264"
"sha2": "0d662b70bd31f4c7a957db6e3c874f0e117d81ec"
}
,{
"testCaseDescription": "javascript-named-function-delete-replacement-test",
"expectedResult": {
"changes": {
"named-function.js": [
"Deleted the 'anotherFunction' function",
"Deleted the 'myFunction' function",
"Added the 'anotherFunction' function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
45
]
}
},
"summary": "Deleted the 'anotherFunction' function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
42
]
}
},
"summary": "Deleted the 'myFunction' function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
45
]
}
},
"summary": "Added the 'anotherFunction' function"
}
]
},
"errors": {}
@ -90,16 +338,30 @@
"filePaths": [
"named-function.js"
],
"sha1": "061e26b3f1bf6b9e8ee101e8dbbf1e0b24796264",
"sha1": "0d662b70bd31f4c7a957db6e3c874f0e117d81ec",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9ce7f161951d99a3690f13549c5cdaf4553214bc"
"sha2": "2751fd48810beeaf43dbb897d5687e7bb4605ee8"
}
,{
"testCaseDescription": "javascript-named-function-delete-test",
"expectedResult": {
"changes": {
"named-function.js": [
"Deleted the 'myFunction' function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
42
]
}
},
"summary": "Deleted the 'myFunction' function"
}
]
},
"errors": {}
@ -107,16 +369,30 @@
"filePaths": [
"named-function.js"
],
"sha1": "9ce7f161951d99a3690f13549c5cdaf4553214bc",
"sha1": "2751fd48810beeaf43dbb897d5687e7bb4605ee8",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7b0b0fac98f3fee5db6238c3532374407e994ac0"
"sha2": "71fbb6e60978e220e6e2f91e426df58fc0fd8317"
}
,{
"testCaseDescription": "javascript-named-function-delete-rest-test",
"expectedResult": {
"changes": {
"named-function.js": [
"Deleted the 'anotherFunction' function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
45
]
}
},
"summary": "Deleted the 'anotherFunction' function"
}
]
},
"errors": {}
@ -124,7 +400,7 @@
"filePaths": [
"named-function.js"
],
"sha1": "7b0b0fac98f3fee5db6238c3532374407e994ac0",
"sha1": "71fbb6e60978e220e6e2f91e426df58fc0fd8317",
"gitDir": "test/corpus/repos/javascript",
"sha2": "733ae2c2622361c892fe98fdad05f30f654595e3"
"sha2": "224d24020b3b8d08a8f3aced4b83b49a5779ba41"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"nested-functions.js": [
"Added the 'parent' function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
103
]
}
},
"summary": "Added the 'parent' function"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"nested-functions.js"
],
"sha1": "5138a3d72bd9c399737de105fe3d5672dc109bc0",
"sha1": "af0eafa72dc7a6795507858b2c2f9ceee614de07",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f2f9ed65976ca856512535c5edfd7a3ca76769e0"
"sha2": "71935f67586876686341a26b8cb2a41794820a6f"
}
,{
"testCaseDescription": "javascript-nested-functions-replacement-insert-test",
"expectedResult": {
"changes": {
"nested-functions.js": [
"Added the 'parent' function",
"Added the 'parent' function"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
103
]
}
},
"summary": "Added the 'parent' function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
103
]
}
},
"summary": "Added the 'parent' function"
}
]
},
"errors": {}
@ -29,17 +71,69 @@
"filePaths": [
"nested-functions.js"
],
"sha1": "f2f9ed65976ca856512535c5edfd7a3ca76769e0",
"sha1": "71935f67586876686341a26b8cb2a41794820a6f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "198bd1571972313ae3c60ad547ced32dfe40a00d"
"sha2": "4ea4f4876b9375f13a68d7254ad672d07b722fdf"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-insert-test",
"expectedResult": {
"changes": {
"nested-functions.js": [
"Replaced the 'arg1' identifier with the 'arg3' identifier in the console.log(arg3) method call of the 'child' function",
"Replaced the 'arg2' identifier with the 'arg4' identifier in the console.log(arg4) method call of the 'child' function"
{
"span": {
"replace": [
{
"start": [
1,
74
],
"end": [
1,
78
]
},
{
"start": [
1,
74
],
"end": [
1,
78
]
}
]
},
"summary": "Replaced the 'arg1' identifier with the 'arg3' identifier in the console.log(arg3) method call of the 'child' function"
},
{
"span": {
"replace": [
{
"start": [
1,
93
],
"end": [
1,
97
]
},
{
"start": [
1,
93
],
"end": [
1,
97
]
}
]
},
"summary": "Replaced the 'arg2' identifier with the 'arg4' identifier in the console.log(arg4) method call of the 'child' function"
}
]
},
"errors": {}
@ -47,17 +141,69 @@
"filePaths": [
"nested-functions.js"
],
"sha1": "198bd1571972313ae3c60ad547ced32dfe40a00d",
"sha1": "4ea4f4876b9375f13a68d7254ad672d07b722fdf",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b7c8942e45be96038e4d80d0711a77d2e9f49684"
"sha2": "be32782b7ddcfa08396ac01c82e30bf7b1df40e7"
}
,{
"testCaseDescription": "javascript-nested-functions-replacement-test",
"expectedResult": {
"changes": {
"nested-functions.js": [
"Replaced the 'arg3' identifier with the 'arg1' identifier in the console.log(arg1) method call of the 'child' function",
"Replaced the 'arg4' identifier with the 'arg2' identifier in the console.log(arg2) method call of the 'child' function"
{
"span": {
"replace": [
{
"start": [
1,
74
],
"end": [
1,
78
]
},
{
"start": [
1,
74
],
"end": [
1,
78
]
}
]
},
"summary": "Replaced the 'arg3' identifier with the 'arg1' identifier in the console.log(arg1) method call of the 'child' function"
},
{
"span": {
"replace": [
{
"start": [
1,
93
],
"end": [
1,
97
]
},
{
"start": [
1,
93
],
"end": [
1,
97
]
}
]
},
"summary": "Replaced the 'arg4' identifier with the 'arg2' identifier in the console.log(arg2) method call of the 'child' function"
}
]
},
"errors": {}
@ -65,18 +211,60 @@
"filePaths": [
"nested-functions.js"
],
"sha1": "b7c8942e45be96038e4d80d0711a77d2e9f49684",
"sha1": "be32782b7ddcfa08396ac01c82e30bf7b1df40e7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2f345e289251ba05901f7a8df887fad0c376f48d"
"sha2": "550a976d210674327b23b298e527abe2b58dec79"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-replacement-test",
"expectedResult": {
"changes": {
"nested-functions.js": [
"Deleted the 'parent' function",
"Deleted the 'parent' function",
"Added the 'parent' function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
103
]
}
},
"summary": "Deleted the 'parent' function"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
103
]
}
},
"summary": "Deleted the 'parent' function"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
103
]
}
},
"summary": "Added the 'parent' function"
}
]
},
"errors": {}
@ -84,16 +272,30 @@
"filePaths": [
"nested-functions.js"
],
"sha1": "2f345e289251ba05901f7a8df887fad0c376f48d",
"sha1": "550a976d210674327b23b298e527abe2b58dec79",
"gitDir": "test/corpus/repos/javascript",
"sha2": "94da54e81e603635014314202fcf2b74913647e1"
"sha2": "cfd77d1d21ca5a1425846fe50bc154ce78ad5e6f"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-test",
"expectedResult": {
"changes": {
"nested-functions.js": [
"Deleted the 'parent' function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
103
]
}
},
"summary": "Deleted the 'parent' function"
}
]
},
"errors": {}
@ -101,16 +303,30 @@
"filePaths": [
"nested-functions.js"
],
"sha1": "94da54e81e603635014314202fcf2b74913647e1",
"sha1": "cfd77d1d21ca5a1425846fe50bc154ce78ad5e6f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f5f6f86cc9874c50455630788910d68f7dcc9ffc"
"sha2": "75785663836095672233edd2495ec92237d0dbcc"
}
,{
"testCaseDescription": "javascript-nested-functions-delete-rest-test",
"expectedResult": {
"changes": {
"nested-functions.js": [
"Deleted the 'parent' function"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
103
]
}
},
"summary": "Deleted the 'parent' function"
}
]
},
"errors": {}
@ -118,7 +334,7 @@
"filePaths": [
"nested-functions.js"
],
"sha1": "f5f6f86cc9874c50455630788910d68f7dcc9ffc",
"sha1": "75785663836095672233edd2495ec92237d0dbcc",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6b39f9fea550c7e75e05c9fe7e2cc13ce4685d6b"
"sha2": "02b2a7bb2b9b4d27a06afbe6d147ca70e6eccf1a"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"null.js": [
"Added the 'null' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Added the 'null' identifier"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"null.js"
],
"sha1": "a089d3a69cf2a56aa770c7f9446691ddd6edfac2",
"sha1": "0eb0a48a27bc6b8d01a210eea8cbccab5c6823f7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "733e761309034c88fb17a205a5f18e9871b69ae0"
"sha2": "921a57a0891031baea0fa0ebfc5c1270751eb7c3"
}
,{
"testCaseDescription": "javascript-null-replacement-insert-test",
"expectedResult": {
"changes": {
"null.js": [
"Added the 'null' return statement",
"Added the 'null' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'null' return statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
5
]
}
},
"summary": "Added the 'null' identifier"
}
]
},
"errors": {}
@ -29,17 +71,45 @@
"filePaths": [
"null.js"
],
"sha1": "733e761309034c88fb17a205a5f18e9871b69ae0",
"sha1": "921a57a0891031baea0fa0ebfc5c1270751eb7c3",
"gitDir": "test/corpus/repos/javascript",
"sha2": "da1b3ff9d481281fb04e00f1d0fd09096b871ae2"
"sha2": "1f137a24235834a5454a98078d3abb07cbdf1063"
}
,{
"testCaseDescription": "javascript-null-delete-insert-test",
"expectedResult": {
"changes": {
"null.js": [
"Added the 'null' identifier",
"Deleted the 'null' return statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Added the 'null' identifier"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'null' return statement"
}
]
},
"errors": {}
@ -47,17 +117,45 @@
"filePaths": [
"null.js"
],
"sha1": "da1b3ff9d481281fb04e00f1d0fd09096b871ae2",
"sha1": "1f137a24235834a5454a98078d3abb07cbdf1063",
"gitDir": "test/corpus/repos/javascript",
"sha2": "08bfb6ab2fce2f4f85195451db434fa8944c9148"
"sha2": "1a76251123795db3deefceda4488e44d2eb80193"
}
,{
"testCaseDescription": "javascript-null-replacement-test",
"expectedResult": {
"changes": {
"null.js": [
"Added the 'null' return statement",
"Deleted the 'null' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'null' return statement"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Deleted the 'null' identifier"
}
]
},
"errors": {}
@ -65,18 +163,60 @@
"filePaths": [
"null.js"
],
"sha1": "08bfb6ab2fce2f4f85195451db434fa8944c9148",
"sha1": "1a76251123795db3deefceda4488e44d2eb80193",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6b61c03a858b3a67fba6cf4a83ff90d1495c54f2"
"sha2": "a7adbf72c2079adee39b2dbcc46a29447cc5b452"
}
,{
"testCaseDescription": "javascript-null-delete-replacement-test",
"expectedResult": {
"changes": {
"null.js": [
"Deleted the 'null' return statement",
"Deleted the 'null' identifier",
"Added the 'null' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'null' return statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
5
]
}
},
"summary": "Deleted the 'null' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Added the 'null' return statement"
}
]
},
"errors": {}
@ -84,16 +224,30 @@
"filePaths": [
"null.js"
],
"sha1": "6b61c03a858b3a67fba6cf4a83ff90d1495c54f2",
"sha1": "a7adbf72c2079adee39b2dbcc46a29447cc5b452",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ac37dc48832d3f1c14c44a84525808a1aea69c42"
"sha2": "72144a33117dda641088c950e9ba56808c39d69d"
}
,{
"testCaseDescription": "javascript-null-delete-test",
"expectedResult": {
"changes": {
"null.js": [
"Deleted the 'null' identifier"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Deleted the 'null' identifier"
}
]
},
"errors": {}
@ -101,16 +255,30 @@
"filePaths": [
"null.js"
],
"sha1": "ac37dc48832d3f1c14c44a84525808a1aea69c42",
"sha1": "72144a33117dda641088c950e9ba56808c39d69d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "32134cb9c8d4e36e48b8453a331dfeb2e611746f"
"sha2": "7985243cb79eac510cc068710b58cff711ca4df7"
}
,{
"testCaseDescription": "javascript-null-delete-rest-test",
"expectedResult": {
"changes": {
"null.js": [
"Deleted the 'null' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'null' return statement"
}
]
},
"errors": {}
@ -118,7 +286,7 @@
"filePaths": [
"null.js"
],
"sha1": "32134cb9c8d4e36e48b8453a331dfeb2e611746f",
"sha1": "7985243cb79eac510cc068710b58cff711ca4df7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "baaf540faedf1f9d3d4dbb4da81b68f94cdd18f4"
"sha2": "0785f1ff3205013dcbd5f5ca4d172e25f57b5969"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"number.js": [
"Added '101'"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Added '101'"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"number.js"
],
"sha1": "3125456796285d13eccdcae2e982892d0ef77ce3",
"sha1": "f5a546c68e4e82d0b350e3e9674659e65c938c55",
"gitDir": "test/corpus/repos/javascript",
"sha2": "8df8993ce19e2156904c501dd8132ef5452cdea3"
"sha2": "47960ec40f3ccbcb1153c70f228c9938575ab8ad"
}
,{
"testCaseDescription": "javascript-number-replacement-insert-test",
"expectedResult": {
"changes": {
"number.js": [
"Added '102'",
"Added '101'"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Added '102'"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
4
]
}
},
"summary": "Added '101'"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"number.js"
],
"sha1": "8df8993ce19e2156904c501dd8132ef5452cdea3",
"sha1": "47960ec40f3ccbcb1153c70f228c9938575ab8ad",
"gitDir": "test/corpus/repos/javascript",
"sha2": "39a95678e0570dc6294c56bde5b1a03558c413de"
"sha2": "06220f52068d26a6bcf0d23f6be481825f7923a4"
}
,{
"testCaseDescription": "javascript-number-delete-insert-test",
"expectedResult": {
"changes": {
"number.js": [
"Replaced '102' with '101'"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
4
]
},
{
"start": [
1,
1
],
"end": [
1,
4
]
}
]
},
"summary": "Replaced '102' with '101'"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"number.js"
],
"sha1": "39a95678e0570dc6294c56bde5b1a03558c413de",
"sha1": "06220f52068d26a6bcf0d23f6be481825f7923a4",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6eab245e2c7b91f5638deb75158a025816129ad5"
"sha2": "404abb4553e8356df1399600d506705c6c9b3ab6"
}
,{
"testCaseDescription": "javascript-number-replacement-test",
"expectedResult": {
"changes": {
"number.js": [
"Replaced '101' with '102'"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
4
]
},
{
"start": [
1,
1
],
"end": [
1,
4
]
}
]
},
"summary": "Replaced '101' with '102'"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"number.js"
],
"sha1": "6eab245e2c7b91f5638deb75158a025816129ad5",
"sha1": "404abb4553e8356df1399600d506705c6c9b3ab6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2f53e1f23e1f1f9b55c2d2b480437cdab3b38a79"
"sha2": "7036f73a00a5222e5d9d889fe5b47ef4d77478b9"
}
,{
"testCaseDescription": "javascript-number-delete-replacement-test",
"expectedResult": {
"changes": {
"number.js": [
"Deleted '102'",
"Deleted '101'",
"Added '102'"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Deleted '102'"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
4
]
}
},
"summary": "Deleted '101'"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
4
]
}
},
"summary": "Added '102'"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"number.js"
],
"sha1": "2f53e1f23e1f1f9b55c2d2b480437cdab3b38a79",
"sha1": "7036f73a00a5222e5d9d889fe5b47ef4d77478b9",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a6e306e2dcd2adb5ecde48feae261627fa2d3b6e"
"sha2": "20984d5e617ddcbc04c1e539365976b48ba4c5e2"
}
,{
"testCaseDescription": "javascript-number-delete-test",
"expectedResult": {
"changes": {
"number.js": [
"Deleted '101'"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Deleted '101'"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"number.js"
],
"sha1": "a6e306e2dcd2adb5ecde48feae261627fa2d3b6e",
"sha1": "20984d5e617ddcbc04c1e539365976b48ba4c5e2",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9190306dca847f3167ee7abd20e298fe69293b6d"
"sha2": "a2dd3c4c8887c73ef3ade2a1e819266cf421eca5"
}
,{
"testCaseDescription": "javascript-number-delete-rest-test",
"expectedResult": {
"changes": {
"number.js": [
"Deleted '102'"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
4
]
}
},
"summary": "Deleted '102'"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"number.js"
],
"sha1": "9190306dca847f3167ee7abd20e298fe69293b6d",
"sha1": "a2dd3c4c8887c73ef3ade2a1e819266cf421eca5",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ff7982a5abb0149fc5cd9e70597748c467270bbc"
"sha2": "743cb64f1ee8a3d9f0b4ea142f1a7e8447757885"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"objects-with-methods.js": [
"Added the '{ add }' object"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Added the '{ add }' object"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"objects-with-methods.js"
],
"sha1": "90db4ab800b9884b43e51ab27b8200dcf2e6c3d7",
"sha1": "9dbca3237fd8109ff6cad0cb5060962d58f10b6c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a49f28e0b4491404337007a99ffc37e7aa6d90be"
"sha2": "394896ec5ce46aa45a7fc7410424fd8682a2a70c"
}
,{
"testCaseDescription": "javascript-objects-with-methods-replacement-insert-test",
"expectedResult": {
"changes": {
"objects-with-methods.js": [
"Added the '{ subtract }' object",
"Added the '{ add }' object"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
37
]
}
},
"summary": "Added the '{ subtract }' object"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
32
]
}
},
"summary": "Added the '{ add }' object"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"objects-with-methods.js"
],
"sha1": "a49f28e0b4491404337007a99ffc37e7aa6d90be",
"sha1": "394896ec5ce46aa45a7fc7410424fd8682a2a70c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ed81a70e5dd77d1562a28c30a7c61a5f5174c8ea"
"sha2": "e560db785a8c18a5f977a29c818a72926c4650ad"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-insert-test",
"expectedResult": {
"changes": {
"objects-with-methods.js": [
"Replaced the 'subtract' identifier with the 'add' identifier in the add method"
{
"span": {
"replace": [
{
"start": [
1,
3
],
"end": [
1,
11
]
},
{
"start": [
1,
3
],
"end": [
1,
6
]
}
]
},
"summary": "Replaced the 'subtract' identifier with the 'add' identifier in the add method"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"objects-with-methods.js"
],
"sha1": "ed81a70e5dd77d1562a28c30a7c61a5f5174c8ea",
"sha1": "e560db785a8c18a5f977a29c818a72926c4650ad",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0cd63cb6e3757f1c6d4c1e7420c8e74ab1daf848"
"sha2": "62fd8c060f49723f91a0f405b48fe9590f519db8"
}
,{
"testCaseDescription": "javascript-objects-with-methods-replacement-test",
"expectedResult": {
"changes": {
"objects-with-methods.js": [
"Replaced the 'add' identifier with the 'subtract' identifier in the subtract method"
{
"span": {
"replace": [
{
"start": [
1,
3
],
"end": [
1,
6
]
},
{
"start": [
1,
3
],
"end": [
1,
11
]
}
]
},
"summary": "Replaced the 'add' identifier with the 'subtract' identifier in the subtract method"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"objects-with-methods.js"
],
"sha1": "0cd63cb6e3757f1c6d4c1e7420c8e74ab1daf848",
"sha1": "62fd8c060f49723f91a0f405b48fe9590f519db8",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f6773b9cdcfe47ab56412c4a8c542dc4d7da84b3"
"sha2": "381f0d3aa4e0c53b425eb42b9f3216c07aa5c3bb"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-replacement-test",
"expectedResult": {
"changes": {
"objects-with-methods.js": [
"Deleted the '{ subtract }' object",
"Deleted the '{ add }' object",
"Added the '{ subtract }' object"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
37
]
}
},
"summary": "Deleted the '{ subtract }' object"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
32
]
}
},
"summary": "Deleted the '{ add }' object"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
37
]
}
},
"summary": "Added the '{ subtract }' object"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"objects-with-methods.js"
],
"sha1": "f6773b9cdcfe47ab56412c4a8c542dc4d7da84b3",
"sha1": "381f0d3aa4e0c53b425eb42b9f3216c07aa5c3bb",
"gitDir": "test/corpus/repos/javascript",
"sha2": "db8c23d90bf179d8b4b5d768192e7a02047468cc"
"sha2": "e86ec26bc3f4e22c3bef80eae7f4afbe9c3b641d"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-test",
"expectedResult": {
"changes": {
"objects-with-methods.js": [
"Deleted the '{ add }' object"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Deleted the '{ add }' object"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"objects-with-methods.js"
],
"sha1": "db8c23d90bf179d8b4b5d768192e7a02047468cc",
"sha1": "e86ec26bc3f4e22c3bef80eae7f4afbe9c3b641d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "93699a8993b936895a94a74dcbc584884ff6f8e1"
"sha2": "04fb0de0a79aef0c8d6160504a7489dae59b7322"
}
,{
"testCaseDescription": "javascript-objects-with-methods-delete-rest-test",
"expectedResult": {
"changes": {
"objects-with-methods.js": [
"Deleted the '{ subtract }' object"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
37
]
}
},
"summary": "Deleted the '{ subtract }' object"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"objects-with-methods.js"
],
"sha1": "93699a8993b936895a94a74dcbc584884ff6f8e1",
"sha1": "04fb0de0a79aef0c8d6160504a7489dae59b7322",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0b47fd2c7f49dd3fb9346a8e02dbfa749c964dec"
"sha2": "f10a454e09922f6b39b73d7a2d1c490a2a4b6179"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"object.js": [
"Added the '{ \"key1\": … }' object"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
21
]
}
},
"summary": "Added the '{ \"key1\": … }' object"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"object.js"
],
"sha1": "f7d88a07b742fd7334d28806f01764ddfed94384",
"sha1": "aefeb00bb872d8308fb1f9989a0b30bee53f794e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "eaec8dce5b0e38f66b0d0672b3516041042aae43"
"sha2": "8d7f9432e5eccbac5a2dce503cb6e9aabe691f64"
}
,{
"testCaseDescription": "javascript-object-replacement-insert-test",
"expectedResult": {
"changes": {
"object.js": [
"Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object",
"Added the '{ \"key1\": … }' object"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
54
]
}
},
"summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
21
]
}
},
"summary": "Added the '{ \"key1\": … }' object"
}
]
},
"errors": {}
@ -29,17 +71,45 @@
"filePaths": [
"object.js"
],
"sha1": "eaec8dce5b0e38f66b0d0672b3516041042aae43",
"sha1": "8d7f9432e5eccbac5a2dce503cb6e9aabe691f64",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a21e93dc503d2b501a94157c2ac07e30bc169a0e"
"sha2": "d4b9e799adb79bd4cc813ce5b7a528e65956b227"
}
,{
"testCaseDescription": "javascript-object-delete-insert-test",
"expectedResult": {
"changes": {
"object.js": [
"Deleted the '\"key2\": …' pair",
"Deleted the '\"key3\": …' pair"
{
"span": {
"delete": {
"start": [
1,
21
],
"end": [
1,
37
]
}
},
"summary": "Deleted the '\"key2\": …' pair"
},
{
"span": {
"delete": {
"start": [
1,
39
],
"end": [
1,
52
]
}
},
"summary": "Deleted the '\"key3\": …' pair"
}
]
},
"errors": {}
@ -47,17 +117,45 @@
"filePaths": [
"object.js"
],
"sha1": "a21e93dc503d2b501a94157c2ac07e30bc169a0e",
"sha1": "d4b9e799adb79bd4cc813ce5b7a528e65956b227",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6935beb9977a9263697acd92b6e4e9ded0f6281e"
"sha2": "181fb7d0795181379db61ff3d91e73e17a7f0176"
}
,{
"testCaseDescription": "javascript-object-replacement-test",
"expectedResult": {
"changes": {
"object.js": [
"Added the '\"key2\": …' pair",
"Added the '\"key3\": …' pair"
{
"span": {
"insert": {
"start": [
1,
21
],
"end": [
1,
37
]
}
},
"summary": "Added the '\"key2\": …' pair"
},
{
"span": {
"insert": {
"start": [
1,
39
],
"end": [
1,
52
]
}
},
"summary": "Added the '\"key3\": …' pair"
}
]
},
"errors": {}
@ -65,18 +163,60 @@
"filePaths": [
"object.js"
],
"sha1": "6935beb9977a9263697acd92b6e4e9ded0f6281e",
"sha1": "181fb7d0795181379db61ff3d91e73e17a7f0176",
"gitDir": "test/corpus/repos/javascript",
"sha2": "bb314ca3df12137d4a1713e5a832235f3a83d1f8"
"sha2": "48b14e07a2432070ba8edc7a97b3a3f5744c4f95"
}
,{
"testCaseDescription": "javascript-object-delete-replacement-test",
"expectedResult": {
"changes": {
"object.js": [
"Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object",
"Deleted the '{ \"key1\": … }' object",
"Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
54
]
}
},
"summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
21
]
}
},
"summary": "Deleted the '{ \"key1\": … }' object"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
54
]
}
},
"summary": "Added the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object"
}
]
},
"errors": {}
@ -84,16 +224,30 @@
"filePaths": [
"object.js"
],
"sha1": "bb314ca3df12137d4a1713e5a832235f3a83d1f8",
"sha1": "48b14e07a2432070ba8edc7a97b3a3f5744c4f95",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6ece14ab8fb09b7072c8d7f5c59a1fff5add4763"
"sha2": "76e45b38000091fee41bc0a0a9f3a5cd65c5492d"
}
,{
"testCaseDescription": "javascript-object-delete-test",
"expectedResult": {
"changes": {
"object.js": [
"Deleted the '{ \"key1\": … }' object"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
21
]
}
},
"summary": "Deleted the '{ \"key1\": … }' object"
}
]
},
"errors": {}
@ -101,16 +255,30 @@
"filePaths": [
"object.js"
],
"sha1": "6ece14ab8fb09b7072c8d7f5c59a1fff5add4763",
"sha1": "76e45b38000091fee41bc0a0a9f3a5cd65c5492d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "cdd370993bbd07183e162146c159e63c0df86618"
"sha2": "2a18894fa97cf6cfb430156aa4a2e0acee543c4c"
}
,{
"testCaseDescription": "javascript-object-delete-rest-test",
"expectedResult": {
"changes": {
"object.js": [
"Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
54
]
}
},
"summary": "Deleted the '{ \"key1\": …, \"key2\": …, \"key3\": … }' object"
}
]
},
"errors": {}
@ -118,7 +286,7 @@
"filePaths": [
"object.js"
],
"sha1": "cdd370993bbd07183e162146c159e63c0df86618",
"sha1": "2a18894fa97cf6cfb430156aa4a2e0acee543c4c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9da531dab73d3a68d171641dcc1913ad7225de16"
"sha2": "0f272e863d223922521e94218a6aace378859dde"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"regex.js": [
"Added the '/one/g' regex"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Added the '/one/g' regex"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"regex.js"
],
"sha1": "0c5416c3cc4fe3d23080c580f0a962802b756bac",
"sha1": "af8dfb899e64bd94fbe9b1d763d771e5140c1334",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a63f4ce54a7fb98a84617b4dd94798d724824ee6"
"sha2": "5c553b5de509611f50d8cea38e7bc08712e40f84"
}
,{
"testCaseDescription": "javascript-regex-replacement-insert-test",
"expectedResult": {
"changes": {
"regex.js": [
"Added the '/on[^/]afe/gim' regex",
"Added the '/one/g' regex"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
15
]
}
},
"summary": "Added the '/on[^/]afe/gim' regex"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Added the '/one/g' regex"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"regex.js"
],
"sha1": "a63f4ce54a7fb98a84617b4dd94798d724824ee6",
"sha1": "5c553b5de509611f50d8cea38e7bc08712e40f84",
"gitDir": "test/corpus/repos/javascript",
"sha2": "85bd846cc470b707c4ec1c48a6732d663fdb5a9a"
"sha2": "62fa5611314d347cba6ca512031b7e98d7ed9d29"
}
,{
"testCaseDescription": "javascript-regex-delete-insert-test",
"expectedResult": {
"changes": {
"regex.js": [
"Replaced the '/on[^/]afe/gim' regex with the '/one/g' regex"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
15
]
},
{
"start": [
1,
1
],
"end": [
1,
7
]
}
]
},
"summary": "Replaced the '/on[^/]afe/gim' regex with the '/one/g' regex"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"regex.js"
],
"sha1": "85bd846cc470b707c4ec1c48a6732d663fdb5a9a",
"sha1": "62fa5611314d347cba6ca512031b7e98d7ed9d29",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a7f7cede434ad189327fa0e7fa685c49cdb95d50"
"sha2": "405e7ab802aa3db2bac92cdb20f99bf410c57dbc"
}
,{
"testCaseDescription": "javascript-regex-replacement-test",
"expectedResult": {
"changes": {
"regex.js": [
"Replaced the '/one/g' regex with the '/on[^/]afe/gim' regex"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
7
]
},
{
"start": [
1,
1
],
"end": [
1,
15
]
}
]
},
"summary": "Replaced the '/one/g' regex with the '/on[^/]afe/gim' regex"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"regex.js"
],
"sha1": "a7f7cede434ad189327fa0e7fa685c49cdb95d50",
"sha1": "405e7ab802aa3db2bac92cdb20f99bf410c57dbc",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5418e08318ecfe12758e4bdc646f3c6a2cbecea1"
"sha2": "4884de88825e39386b25a8e169e393739c8bce7f"
}
,{
"testCaseDescription": "javascript-regex-delete-replacement-test",
"expectedResult": {
"changes": {
"regex.js": [
"Deleted the '/on[^/]afe/gim' regex",
"Deleted the '/one/g' regex",
"Added the '/on[^/]afe/gim' regex"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
15
]
}
},
"summary": "Deleted the '/on[^/]afe/gim' regex"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Deleted the '/one/g' regex"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
15
]
}
},
"summary": "Added the '/on[^/]afe/gim' regex"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"regex.js"
],
"sha1": "5418e08318ecfe12758e4bdc646f3c6a2cbecea1",
"sha1": "4884de88825e39386b25a8e169e393739c8bce7f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6411dd0288384ca73b9777381c279c6c7f22419c"
"sha2": "6c23a5a1bd35e05cad7084429ae5cca16951c4dd"
}
,{
"testCaseDescription": "javascript-regex-delete-test",
"expectedResult": {
"changes": {
"regex.js": [
"Deleted the '/one/g' regex"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the '/one/g' regex"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"regex.js"
],
"sha1": "6411dd0288384ca73b9777381c279c6c7f22419c",
"sha1": "6c23a5a1bd35e05cad7084429ae5cca16951c4dd",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7304eb7a6b3f45f80c964a7649a77c2dc0e8cd9e"
"sha2": "ab5b91f92abd2e34adfba5a1819cbe1c84ec0e65"
}
,{
"testCaseDescription": "javascript-regex-delete-rest-test",
"expectedResult": {
"changes": {
"regex.js": [
"Deleted the '/on[^/]afe/gim' regex"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
15
]
}
},
"summary": "Deleted the '/on[^/]afe/gim' regex"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"regex.js"
],
"sha1": "7304eb7a6b3f45f80c964a7649a77c2dc0e8cd9e",
"sha1": "ab5b91f92abd2e34adfba5a1819cbe1c84ec0e65",
"gitDir": "test/corpus/repos/javascript",
"sha2": "57c773af116921575b844893c03a256cc1464667"
"sha2": "b5b96ac96b0968b5b9d02ce5844f7274e13f3554"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"relational-operator.js": [
"Added the 'x < y' relational operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Added the 'x < y' relational operator"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"relational-operator.js"
],
"sha1": "b7fa6094450d8736147677929ef398854de0ac66",
"sha1": "707d6d491b49e1d91b26dc55086e140e997fcaf4",
"gitDir": "test/corpus/repos/javascript",
"sha2": "80d9012d97ce07f35e94f9a0cd65567d62164d25"
"sha2": "916c235b3685819d8f98b4805abe2a2f863cee37"
}
,{
"testCaseDescription": "javascript-relational-operator-replacement-insert-test",
"expectedResult": {
"changes": {
"relational-operator.js": [
"Added the 'x <= y' relational operator",
"Added the 'x < y' relational operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Added the 'x <= y' relational operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
6
]
}
},
"summary": "Added the 'x < y' relational operator"
}
]
},
"errors": {}
@ -29,9 +71,9 @@
"filePaths": [
"relational-operator.js"
],
"sha1": "80d9012d97ce07f35e94f9a0cd65567d62164d25",
"sha1": "916c235b3685819d8f98b4805abe2a2f863cee37",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d45f155c6a91dbf64063b61bdc7441dad3d7af67"
"sha2": "fe34e80ceab52842be3fae1f56c762da6716100f"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-insert-test",
@ -42,9 +84,9 @@
"filePaths": [
"relational-operator.js"
],
"sha1": "d45f155c6a91dbf64063b61bdc7441dad3d7af67",
"sha1": "fe34e80ceab52842be3fae1f56c762da6716100f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b601efb23e50c6c5437e2b7ee5db57dd37055ae9"
"sha2": "12ace7b189aaa7cd68b7735eafa5ba5af428222e"
}
,{
"testCaseDescription": "javascript-relational-operator-replacement-test",
@ -55,16 +97,30 @@
"filePaths": [
"relational-operator.js"
],
"sha1": "b601efb23e50c6c5437e2b7ee5db57dd37055ae9",
"sha1": "12ace7b189aaa7cd68b7735eafa5ba5af428222e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "fa72dfb24e5ce035bea38fe6e17d7aaacee750cc"
"sha2": "fd43a8853b4536d9b2cfb81fac73ab21a59ecb7d"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-replacement-test",
"expectedResult": {
"changes": {
"relational-operator.js": [
"Deleted the 'x <= y' relational operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'x <= y' relational operator"
}
]
},
"errors": {}
@ -72,16 +128,30 @@
"filePaths": [
"relational-operator.js"
],
"sha1": "fa72dfb24e5ce035bea38fe6e17d7aaacee750cc",
"sha1": "fd43a8853b4536d9b2cfb81fac73ab21a59ecb7d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b16c7ec47ca3569a228b1414ba00722ac44a4b55"
"sha2": "76f7572bb3b4761c61b2234b8078fc3dbb74b214"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-test",
"expectedResult": {
"changes": {
"relational-operator.js": [
"Deleted the 'x < y' relational operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
6
]
}
},
"summary": "Deleted the 'x < y' relational operator"
}
]
},
"errors": {}
@ -89,16 +159,30 @@
"filePaths": [
"relational-operator.js"
],
"sha1": "b16c7ec47ca3569a228b1414ba00722ac44a4b55",
"sha1": "76f7572bb3b4761c61b2234b8078fc3dbb74b214",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a3267f7db8d8e4233e48b74ce15aa1504462957a"
"sha2": "4f1db5cef124c17f6473e7fca95c07ae3f84a4f9"
}
,{
"testCaseDescription": "javascript-relational-operator-delete-rest-test",
"expectedResult": {
"changes": {
"relational-operator.js": [
"Deleted the 'x <= y' relational operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'x <= y' relational operator"
}
]
},
"errors": {}
@ -106,7 +190,7 @@
"filePaths": [
"relational-operator.js"
],
"sha1": "a3267f7db8d8e4233e48b74ce15aa1504462957a",
"sha1": "4f1db5cef124c17f6473e7fca95c07ae3f84a4f9",
"gitDir": "test/corpus/repos/javascript",
"sha2": "91879997d6cf416704979ff78f40bbb662d3defc"
"sha2": "22f62c999613fdb9f40f1fcabfd6e3900de152cb"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"return-statement.js": [
"Added the '5' return statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
10
]
}
},
"summary": "Added the '5' return statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"return-statement.js"
],
"sha1": "2dd2ec7225c40d31a12625d2ed9365654a4134ec",
"sha1": "f6aaca47eff83aa2dd6a8ce2e41b14394977d9b3",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5e48613012ffe3f1e874c3c64060a4eafedc6b06"
"sha2": "524d62d049c00b51a2cea985dfb7ce08c0b6d073"
}
,{
"testCaseDescription": "javascript-return-statement-replacement-insert-test",
"expectedResult": {
"changes": {
"return-statement.js": [
"Added the 'empty' return statement",
"Added the '5' return statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Added the 'empty' return statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
10
]
}
},
"summary": "Added the '5' return statement"
}
]
},
"errors": {}
@ -29,16 +71,30 @@
"filePaths": [
"return-statement.js"
],
"sha1": "5e48613012ffe3f1e874c3c64060a4eafedc6b06",
"sha1": "524d62d049c00b51a2cea985dfb7ce08c0b6d073",
"gitDir": "test/corpus/repos/javascript",
"sha2": "3add605c5e538b1b85552cc0e890a61ac2fc96a9"
"sha2": "8041d77efbe04a7cd0f2ba66793621e61e0c74e3"
}
,{
"testCaseDescription": "javascript-return-statement-delete-insert-test",
"expectedResult": {
"changes": {
"return-statement.js": [
"Added '5'"
{
"span": {
"insert": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Added '5'"
}
]
},
"errors": {}
@ -46,16 +102,30 @@
"filePaths": [
"return-statement.js"
],
"sha1": "3add605c5e538b1b85552cc0e890a61ac2fc96a9",
"sha1": "8041d77efbe04a7cd0f2ba66793621e61e0c74e3",
"gitDir": "test/corpus/repos/javascript",
"sha2": "efab8a28fc1de4d04cfde2504774b9fb07530fe2"
"sha2": "62102491107e2639f888bcb06ba212d8697cbbaf"
}
,{
"testCaseDescription": "javascript-return-statement-replacement-test",
"expectedResult": {
"changes": {
"return-statement.js": [
"Deleted '5'"
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
9
]
}
},
"summary": "Deleted '5'"
}
]
},
"errors": {}
@ -63,18 +133,60 @@
"filePaths": [
"return-statement.js"
],
"sha1": "efab8a28fc1de4d04cfde2504774b9fb07530fe2",
"sha1": "62102491107e2639f888bcb06ba212d8697cbbaf",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4322b92f93fdadfdc746a59f2a419e5b2753881c"
"sha2": "a9ab5b797c44abed96f142adcfe1da66f0b1a5d4"
}
,{
"testCaseDescription": "javascript-return-statement-delete-replacement-test",
"expectedResult": {
"changes": {
"return-statement.js": [
"Deleted the 'empty' return statement",
"Deleted the '5' return statement",
"Added the 'empty' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'empty' return statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
10
]
}
},
"summary": "Deleted the '5' return statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
8
]
}
},
"summary": "Added the 'empty' return statement"
}
]
},
"errors": {}
@ -82,16 +194,30 @@
"filePaths": [
"return-statement.js"
],
"sha1": "4322b92f93fdadfdc746a59f2a419e5b2753881c",
"sha1": "a9ab5b797c44abed96f142adcfe1da66f0b1a5d4",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2972b369c2cb319df516c9eb8c71a0ac7d2016be"
"sha2": "86d283e41d3acb1a891c8212466478d832e7cf4f"
}
,{
"testCaseDescription": "javascript-return-statement-delete-test",
"expectedResult": {
"changes": {
"return-statement.js": [
"Deleted the '5' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
10
]
}
},
"summary": "Deleted the '5' return statement"
}
]
},
"errors": {}
@ -99,16 +225,30 @@
"filePaths": [
"return-statement.js"
],
"sha1": "2972b369c2cb319df516c9eb8c71a0ac7d2016be",
"sha1": "86d283e41d3acb1a891c8212466478d832e7cf4f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "043a49ed8f9ad253fc37685a4b7a196c88fa1113"
"sha2": "5f60834d911eb278ea13e451d5c62e658f8dd7c4"
}
,{
"testCaseDescription": "javascript-return-statement-delete-rest-test",
"expectedResult": {
"changes": {
"return-statement.js": [
"Deleted the 'empty' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'empty' return statement"
}
]
},
"errors": {}
@ -116,7 +256,7 @@
"filePaths": [
"return-statement.js"
],
"sha1": "043a49ed8f9ad253fc37685a4b7a196c88fa1113",
"sha1": "5f60834d911eb278ea13e451d5c62e658f8dd7c4",
"gitDir": "test/corpus/repos/javascript",
"sha2": "1331b0dc40147173385ee65a3f7a2a1b390bd6dd"
"sha2": "c94930423eb6a6e61d369ac9025d969d2d2e6c1a"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"string.js": [
"Added the 'A string with \"double\" quotes' string"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Added the 'A string with \"double\" quotes' string"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"string.js"
],
"sha1": "0b47fd2c7f49dd3fb9346a8e02dbfa749c964dec",
"sha1": "2c57559d605a6fe81e465c7fab6c70b3ed995911",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ced9d238ce2db329b155ad8c65aaf50c605153ed"
"sha2": "63d3e81fd7d64a832830e004ea516b53f8781779"
}
,{
"testCaseDescription": "javascript-string-replacement-insert-test",
"expectedResult": {
"changes": {
"string.js": [
"Added the 'A different string with \"double\" quotes' string",
"Added the 'A string with \"double\" quotes' string"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
42
]
}
},
"summary": "Added the 'A different string with \"double\" quotes' string"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
32
]
}
},
"summary": "Added the 'A string with \"double\" quotes' string"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"string.js"
],
"sha1": "ced9d238ce2db329b155ad8c65aaf50c605153ed",
"sha1": "63d3e81fd7d64a832830e004ea516b53f8781779",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4bfe4a30ec7fe10b4df1d212852a87a262b317d4"
"sha2": "51fa8e3cc925686b215735182f750faa5820479b"
}
,{
"testCaseDescription": "javascript-string-delete-insert-test",
"expectedResult": {
"changes": {
"string.js": [
"Replaced the 'A different string with \"double\" quotes' string with the 'A string with \"double\" quotes' string"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
42
]
},
{
"start": [
1,
1
],
"end": [
1,
32
]
}
]
},
"summary": "Replaced the 'A different string with \"double\" quotes' string with the 'A string with \"double\" quotes' string"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"string.js"
],
"sha1": "4bfe4a30ec7fe10b4df1d212852a87a262b317d4",
"sha1": "51fa8e3cc925686b215735182f750faa5820479b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "3dad07d1b87319d94fdeac50281d9b08bced32e9"
"sha2": "fd50f8ac493b23fe746ee14b683b6c51af6503ec"
}
,{
"testCaseDescription": "javascript-string-replacement-test",
"expectedResult": {
"changes": {
"string.js": [
"Replaced the 'A string with \"double\" quotes' string with the 'A different string with \"double\" quotes' string"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
32
]
},
{
"start": [
1,
1
],
"end": [
1,
42
]
}
]
},
"summary": "Replaced the 'A string with \"double\" quotes' string with the 'A different string with \"double\" quotes' string"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"string.js"
],
"sha1": "3dad07d1b87319d94fdeac50281d9b08bced32e9",
"sha1": "fd50f8ac493b23fe746ee14b683b6c51af6503ec",
"gitDir": "test/corpus/repos/javascript",
"sha2": "265932250cab015f280e8ac49a1483dbb112c8c1"
"sha2": "890a07342ca69ed4057e75883d8b42275147405d"
}
,{
"testCaseDescription": "javascript-string-delete-replacement-test",
"expectedResult": {
"changes": {
"string.js": [
"Deleted the 'A different string with \"double\" quotes' string",
"Deleted the 'A string with \"double\" quotes' string",
"Added the 'A different string with \"double\" quotes' string"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
42
]
}
},
"summary": "Deleted the 'A different string with \"double\" quotes' string"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
32
]
}
},
"summary": "Deleted the 'A string with \"double\" quotes' string"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
42
]
}
},
"summary": "Added the 'A different string with \"double\" quotes' string"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"string.js"
],
"sha1": "265932250cab015f280e8ac49a1483dbb112c8c1",
"sha1": "890a07342ca69ed4057e75883d8b42275147405d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "684b45d926230d657ba092ef03910ed88b9e59c8"
"sha2": "93afe1101fa2f097436cdbf596d0d8f1f8857999"
}
,{
"testCaseDescription": "javascript-string-delete-test",
"expectedResult": {
"changes": {
"string.js": [
"Deleted the 'A string with \"double\" quotes' string"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
32
]
}
},
"summary": "Deleted the 'A string with \"double\" quotes' string"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"string.js"
],
"sha1": "684b45d926230d657ba092ef03910ed88b9e59c8",
"sha1": "93afe1101fa2f097436cdbf596d0d8f1f8857999",
"gitDir": "test/corpus/repos/javascript",
"sha2": "8ad5bf46e1008a85e76225afb9427012b3bc64d6"
"sha2": "77450417d7c60d4c5e9027dbe758092098a51ad1"
}
,{
"testCaseDescription": "javascript-string-delete-rest-test",
"expectedResult": {
"changes": {
"string.js": [
"Deleted the 'A different string with \"double\" quotes' string"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
42
]
}
},
"summary": "Deleted the 'A different string with \"double\" quotes' string"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"string.js"
],
"sha1": "8ad5bf46e1008a85e76225afb9427012b3bc64d6",
"sha1": "77450417d7c60d4c5e9027dbe758092098a51ad1",
"gitDir": "test/corpus/repos/javascript",
"sha2": "3125456796285d13eccdcae2e982892d0ef77ce3"
"sha2": "2bdf24d58c9431fd69cc73d80180388bb579a170"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"subscript-access-assignment.js": [
"Added the 'y[\"x\"]' assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Added the 'y[\"x\"]' assignment"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"subscript-access-assignment.js"
],
"sha1": "63243f11ee238a04b1c51987a7cbc7d48f5f405b",
"sha1": "64a9a65e90cf48c435d6c1c46b80cf7935b26413",
"gitDir": "test/corpus/repos/javascript",
"sha2": "01f7085186d9284f24e450dc803c0b2b71a0cea7"
"sha2": "0148ee834e361c93f645aa32ac05516803f56d3d"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-replacement-insert-test",
"expectedResult": {
"changes": {
"subscript-access-assignment.js": [
"Added the 'y[\"x\"]' assignment",
"Added the 'y[\"x\"]' assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Added the 'y[\"x\"]' assignment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
11
]
}
},
"summary": "Added the 'y[\"x\"]' assignment"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"subscript-access-assignment.js"
],
"sha1": "01f7085186d9284f24e450dc803c0b2b71a0cea7",
"sha1": "0148ee834e361c93f645aa32ac05516803f56d3d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a98acc349854019c25f83d60321a63d39032bcb5"
"sha2": "bcdee486f71016fc693985b4f6a5d0d472e8c5ff"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-insert-test",
"expectedResult": {
"changes": {
"subscript-access-assignment.js": [
"Replaced '1' with '0' in an assignment to y[\"x\"]"
{
"span": {
"replace": [
{
"start": [
1,
10
],
"end": [
1,
11
]
},
{
"start": [
1,
10
],
"end": [
1,
11
]
}
]
},
"summary": "Replaced '1' with '0' in an assignment to y[\"x\"]"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"subscript-access-assignment.js"
],
"sha1": "a98acc349854019c25f83d60321a63d39032bcb5",
"sha1": "bcdee486f71016fc693985b4f6a5d0d472e8c5ff",
"gitDir": "test/corpus/repos/javascript",
"sha2": "13e950e265f72b4ca2f163d49f076dbbc64c22d5"
"sha2": "7f3bc8ffdd75c0bfba679d28e3d16105a50eb9f8"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-replacement-test",
"expectedResult": {
"changes": {
"subscript-access-assignment.js": [
"Replaced '0' with '1' in an assignment to y[\"x\"]"
{
"span": {
"replace": [
{
"start": [
1,
10
],
"end": [
1,
11
]
},
{
"start": [
1,
10
],
"end": [
1,
11
]
}
]
},
"summary": "Replaced '0' with '1' in an assignment to y[\"x\"]"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"subscript-access-assignment.js"
],
"sha1": "13e950e265f72b4ca2f163d49f076dbbc64c22d5",
"sha1": "7f3bc8ffdd75c0bfba679d28e3d16105a50eb9f8",
"gitDir": "test/corpus/repos/javascript",
"sha2": "99241c059d2da18548b7f996c1cbb71b5ea23605"
"sha2": "c3aff9f350cd0e8260f4a384b249bf7a94e7acb1"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-replacement-test",
"expectedResult": {
"changes": {
"subscript-access-assignment.js": [
"Deleted the 'y[\"x\"]' assignment",
"Deleted the 'y[\"x\"]' assignment",
"Added the 'y[\"x\"]' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'y[\"x\"]' assignment"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
11
]
}
},
"summary": "Deleted the 'y[\"x\"]' assignment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
11
]
}
},
"summary": "Added the 'y[\"x\"]' assignment"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"subscript-access-assignment.js"
],
"sha1": "99241c059d2da18548b7f996c1cbb71b5ea23605",
"sha1": "c3aff9f350cd0e8260f4a384b249bf7a94e7acb1",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9713f00bd14ffc58131e5b92769adf3a689474a1"
"sha2": "f31563441a2e6ad63ed5a261a4f7be1a11b82eac"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-test",
"expectedResult": {
"changes": {
"subscript-access-assignment.js": [
"Deleted the 'y[\"x\"]' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'y[\"x\"]' assignment"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"subscript-access-assignment.js"
],
"sha1": "9713f00bd14ffc58131e5b92769adf3a689474a1",
"sha1": "f31563441a2e6ad63ed5a261a4f7be1a11b82eac",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e2550c3c57d22a532427f1fc72c679a6aaf4338a"
"sha2": "6d226d202513c5c50d0ceb3f3fd85f8d303fcf74"
}
,{
"testCaseDescription": "javascript-subscript-access-assignment-delete-rest-test",
"expectedResult": {
"changes": {
"subscript-access-assignment.js": [
"Deleted the 'y[\"x\"]' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Deleted the 'y[\"x\"]' assignment"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"subscript-access-assignment.js"
],
"sha1": "e2550c3c57d22a532427f1fc72c679a6aaf4338a",
"sha1": "6d226d202513c5c50d0ceb3f3fd85f8d303fcf74",
"gitDir": "test/corpus/repos/javascript",
"sha2": "203f8d67079e4651a60594004213482fbcf7da59"
"sha2": "acc75ec053faa10bfebdd149cbf41d414f3089fb"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"subscript-access-string.js": [
"Added the 'x[\"some-string\"]' subscript access"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
17
]
}
},
"summary": "Added the 'x[\"some-string\"]' subscript access"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"subscript-access-string.js"
],
"sha1": "023c6213d93a53ba32f3853b64d4263f85211f18",
"sha1": "5fb1a0314101669d4cfd005c86d42e20fe86d7c9",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2d3a278f5131fba90fe2dde2defc06cba066eb14"
"sha2": "fa043ac413c9b7b75a82168891b6d00eee678b92"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
23
]
}
},
"summary": "Added the 'x[\"some-other-string\"]' subscript access"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
17
]
}
},
"summary": "Added the 'x[\"some-string\"]' subscript access"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"subscript-access-string.js"
],
"sha1": "2d3a278f5131fba90fe2dde2defc06cba066eb14",
"sha1": "fa043ac413c9b7b75a82168891b6d00eee678b92",
"gitDir": "test/corpus/repos/javascript",
"sha2": "67ee57a0b25eceeb8f74905279abc77bf15413f6"
"sha2": "08a7b1b79627d5ecf2f6c2a44d1c2096d659e096"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-insert-test",
"expectedResult": {
"changes": {
"subscript-access-string.js": [
"Replaced the \"some-other-string\" string with the \"some-string\" string in the x[\"some-string\"] subscript access"
{
"span": {
"replace": [
{
"start": [
1,
3
],
"end": [
1,
22
]
},
{
"start": [
1,
3
],
"end": [
1,
16
]
}
]
},
"summary": "Replaced the \"some-other-string\" string with the \"some-string\" string in the x[\"some-string\"] subscript access"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"subscript-access-string.js"
],
"sha1": "67ee57a0b25eceeb8f74905279abc77bf15413f6",
"sha1": "08a7b1b79627d5ecf2f6c2a44d1c2096d659e096",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6fb419b0fc46357a7290f5d8a80d10a1a55c659e"
"sha2": "f95d1cff9be9bd90156ccd975f57021c1f8eefaa"
}
,{
"testCaseDescription": "javascript-subscript-access-string-replacement-test",
"expectedResult": {
"changes": {
"subscript-access-string.js": [
"Replaced the \"some-string\" string with the \"some-other-string\" string in the x[\"some-other-string\"] subscript access"
{
"span": {
"replace": [
{
"start": [
1,
3
],
"end": [
1,
16
]
},
{
"start": [
1,
3
],
"end": [
1,
22
]
}
]
},
"summary": "Replaced the \"some-string\" string with the \"some-other-string\" string in the x[\"some-other-string\"] subscript access"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"subscript-access-string.js"
],
"sha1": "6fb419b0fc46357a7290f5d8a80d10a1a55c659e",
"sha1": "f95d1cff9be9bd90156ccd975f57021c1f8eefaa",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7c7394304e4a4a8a74e3a68b3f53db1d1e10f870"
"sha2": "b9a70f9be8d0f10a65ec1c067062f2cb065a7f4a"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-replacement-test",
"expectedResult": {
"changes": {
"subscript-access-string.js": [
"Deleted the 'x[\"some-other-string\"]' subscript access",
"Deleted the 'x[\"some-string\"]' subscript access",
"Added the 'x[\"some-other-string\"]' subscript access"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
23
]
}
},
"summary": "Deleted the 'x[\"some-other-string\"]' subscript access"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
17
]
}
},
"summary": "Deleted the 'x[\"some-string\"]' subscript access"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
23
]
}
},
"summary": "Added the 'x[\"some-other-string\"]' subscript access"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"subscript-access-string.js"
],
"sha1": "7c7394304e4a4a8a74e3a68b3f53db1d1e10f870",
"sha1": "b9a70f9be8d0f10a65ec1c067062f2cb065a7f4a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b4fa420e72b62676779d596b582950635a7a6c9a"
"sha2": "ea9a6faa38a6630a573c055d81b574d5c9bbc033"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-test",
"expectedResult": {
"changes": {
"subscript-access-string.js": [
"Deleted the 'x[\"some-string\"]' subscript access"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
17
]
}
},
"summary": "Deleted the 'x[\"some-string\"]' subscript access"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"subscript-access-string.js"
],
"sha1": "b4fa420e72b62676779d596b582950635a7a6c9a",
"sha1": "ea9a6faa38a6630a573c055d81b574d5c9bbc033",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a91f7fd27ab212c691e821acb6026895817df9de"
"sha2": "f49f652c070f4bf8a8a3950fe588b2e0039e5cc4"
}
,{
"testCaseDescription": "javascript-subscript-access-string-delete-rest-test",
"expectedResult": {
"changes": {
"subscript-access-string.js": [
"Deleted the 'x[\"some-other-string\"]' subscript access"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
23
]
}
},
"summary": "Deleted the 'x[\"some-other-string\"]' subscript access"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"subscript-access-string.js"
],
"sha1": "a91f7fd27ab212c691e821acb6026895817df9de",
"sha1": "f49f652c070f4bf8a8a3950fe588b2e0039e5cc4",
"gitDir": "test/corpus/repos/javascript",
"sha2": "3d95b8bc8af09bb93dafc24df379fa1181367357"
"sha2": "b934ce54bbf5097cc87a64591e51df2b0139a940"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"subscript-access-variable.js": [
"Added the 'x[someVariable]' subscript access"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
16
]
}
},
"summary": "Added the 'x[someVariable]' subscript access"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"subscript-access-variable.js"
],
"sha1": "39134301fe3c61d2958c5cd1e72bc40a4945825b",
"sha1": "35771d9839083e28344a82ab572b45449680ab65",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ecde82b5f9ed4d33bd0e38e15ec87141c5c243cb"
"sha2": "dfbfa45cf724b9a16226e8d0410e91ccb69cbbe3"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
21
]
}
},
"summary": "Added the 'x[someOtherVariable]' subscript access"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
16
]
}
},
"summary": "Added the 'x[someVariable]' subscript access"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"subscript-access-variable.js"
],
"sha1": "ecde82b5f9ed4d33bd0e38e15ec87141c5c243cb",
"sha1": "dfbfa45cf724b9a16226e8d0410e91ccb69cbbe3",
"gitDir": "test/corpus/repos/javascript",
"sha2": "c7c2d1bac5dd1af76c3c1ffc1985284733a2616a"
"sha2": "c853b9ef85feb46622a4d7a24542a26e1ceea602"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-insert-test",
"expectedResult": {
"changes": {
"subscript-access-variable.js": [
"Replaced the 'someOtherVariable' identifier with the 'someVariable' identifier in the x[someVariable] subscript access"
{
"span": {
"replace": [
{
"start": [
1,
3
],
"end": [
1,
20
]
},
{
"start": [
1,
3
],
"end": [
1,
15
]
}
]
},
"summary": "Replaced the 'someOtherVariable' identifier with the 'someVariable' identifier in the x[someVariable] subscript access"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"subscript-access-variable.js"
],
"sha1": "c7c2d1bac5dd1af76c3c1ffc1985284733a2616a",
"sha1": "c853b9ef85feb46622a4d7a24542a26e1ceea602",
"gitDir": "test/corpus/repos/javascript",
"sha2": "181dfb7bafff91019d61572cf5e27a445cce14f5"
"sha2": "8c7964617fa9ed63c35663da54e463e1cedebc87"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-replacement-test",
"expectedResult": {
"changes": {
"subscript-access-variable.js": [
"Replaced the 'someVariable' identifier with the 'someOtherVariable' identifier in the x[someOtherVariable] subscript access"
{
"span": {
"replace": [
{
"start": [
1,
3
],
"end": [
1,
15
]
},
{
"start": [
1,
3
],
"end": [
1,
20
]
}
]
},
"summary": "Replaced the 'someVariable' identifier with the 'someOtherVariable' identifier in the x[someOtherVariable] subscript access"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"subscript-access-variable.js"
],
"sha1": "181dfb7bafff91019d61572cf5e27a445cce14f5",
"sha1": "8c7964617fa9ed63c35663da54e463e1cedebc87",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2e978dc878c68bf75bd729ee635d3cff3c56b5e2"
"sha2": "1743980c0a2d957e974333f4a7fe7be2aee103b4"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-replacement-test",
"expectedResult": {
"changes": {
"subscript-access-variable.js": [
"Deleted the 'x[someOtherVariable]' subscript access",
"Deleted the 'x[someVariable]' subscript access",
"Added the 'x[someOtherVariable]' subscript access"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
21
]
}
},
"summary": "Deleted the 'x[someOtherVariable]' subscript access"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
16
]
}
},
"summary": "Deleted the 'x[someVariable]' subscript access"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
21
]
}
},
"summary": "Added the 'x[someOtherVariable]' subscript access"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"subscript-access-variable.js"
],
"sha1": "2e978dc878c68bf75bd729ee635d3cff3c56b5e2",
"sha1": "1743980c0a2d957e974333f4a7fe7be2aee103b4",
"gitDir": "test/corpus/repos/javascript",
"sha2": "913fa8e8e7177b17e6995ee6c6501ff8b2741131"
"sha2": "cfd54e85a90ff88f76612bf060a9cc2f917f5648"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-test",
"expectedResult": {
"changes": {
"subscript-access-variable.js": [
"Deleted the 'x[someVariable]' subscript access"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
16
]
}
},
"summary": "Deleted the 'x[someVariable]' subscript access"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"subscript-access-variable.js"
],
"sha1": "913fa8e8e7177b17e6995ee6c6501ff8b2741131",
"sha1": "cfd54e85a90ff88f76612bf060a9cc2f917f5648",
"gitDir": "test/corpus/repos/javascript",
"sha2": "30fddf9d4fea2f2dc023b45bfd76d311e561b678"
"sha2": "58c32b6f0cb4ee41b2486ed0c4a08c4b7bb91d5b"
}
,{
"testCaseDescription": "javascript-subscript-access-variable-delete-rest-test",
"expectedResult": {
"changes": {
"subscript-access-variable.js": [
"Deleted the 'x[someOtherVariable]' subscript access"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
21
]
}
},
"summary": "Deleted the 'x[someOtherVariable]' subscript access"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"subscript-access-variable.js"
],
"sha1": "30fddf9d4fea2f2dc023b45bfd76d311e561b678",
"sha1": "58c32b6f0cb4ee41b2486ed0c4a08c4b7bb91d5b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "023c6213d93a53ba32f3853b64d4263f85211f18"
"sha2": "07ef5da0087fbbef26cc63b4629a9c05e919a68b"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"switch-statement.js": [
"Added the '1' switch statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
48
]
}
},
"summary": "Added the '1' switch statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"switch-statement.js"
],
"sha1": "9ee63cde4ca79fd99837bf8de8adcd8920b8752b",
"sha1": "d30e43ec820b535d256a20ed0964fba95c8764b3",
"gitDir": "test/corpus/repos/javascript",
"sha2": "42967a58fd3321ea5a6de6db3154296f357c55f1"
"sha2": "6f28b051550ecf618c5ec1fc4109a47787a4da9c"
}
,{
"testCaseDescription": "javascript-switch-statement-replacement-insert-test",
"expectedResult": {
"changes": {
"switch-statement.js": [
"Added the '2' switch statement",
"Added the '1' switch statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
48
]
}
},
"summary": "Added the '2' switch statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
48
]
}
},
"summary": "Added the '1' switch statement"
}
]
},
"errors": {}
@ -29,17 +71,69 @@
"filePaths": [
"switch-statement.js"
],
"sha1": "42967a58fd3321ea5a6de6db3154296f357c55f1",
"sha1": "6f28b051550ecf618c5ec1fc4109a47787a4da9c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "41f5cdac0d7746084cd3fb0a8e160ca8f893d54b"
"sha2": "c7bbc680850439b171c5c39a1dbb8bf3f4b258f1"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-insert-test",
"expectedResult": {
"changes": {
"switch-statement.js": [
"Replaced '2' with '1'",
"Replaced '2' with '1'"
{
"span": {
"replace": [
{
"start": [
1,
9
],
"end": [
1,
10
]
},
{
"start": [
1,
9
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced '2' with '1'"
},
{
"span": {
"replace": [
{
"start": [
1,
33
],
"end": [
1,
34
]
},
{
"start": [
1,
33
],
"end": [
1,
34
]
}
]
},
"summary": "Replaced '2' with '1'"
}
]
},
"errors": {}
@ -47,17 +141,69 @@
"filePaths": [
"switch-statement.js"
],
"sha1": "41f5cdac0d7746084cd3fb0a8e160ca8f893d54b",
"sha1": "c7bbc680850439b171c5c39a1dbb8bf3f4b258f1",
"gitDir": "test/corpus/repos/javascript",
"sha2": "df2369974616b0214995247c70734f44d0d12512"
"sha2": "e1abf04722dcc2abc2e741e80c3d9c5bbaf94ab6"
}
,{
"testCaseDescription": "javascript-switch-statement-replacement-test",
"expectedResult": {
"changes": {
"switch-statement.js": [
"Replaced '1' with '2'",
"Replaced '1' with '2'"
{
"span": {
"replace": [
{
"start": [
1,
9
],
"end": [
1,
10
]
},
{
"start": [
1,
9
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced '1' with '2'"
},
{
"span": {
"replace": [
{
"start": [
1,
33
],
"end": [
1,
34
]
},
{
"start": [
1,
33
],
"end": [
1,
34
]
}
]
},
"summary": "Replaced '1' with '2'"
}
]
},
"errors": {}
@ -65,18 +211,60 @@
"filePaths": [
"switch-statement.js"
],
"sha1": "df2369974616b0214995247c70734f44d0d12512",
"sha1": "e1abf04722dcc2abc2e741e80c3d9c5bbaf94ab6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "c7325fbbeedf0a427a6ce87cd26cf8031ad9bd99"
"sha2": "f3d3fb5a9daeccf22d32dbcf79e3e6db7e00ac2e"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-replacement-test",
"expectedResult": {
"changes": {
"switch-statement.js": [
"Deleted the '2' switch statement",
"Deleted the '1' switch statement",
"Added the '2' switch statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
48
]
}
},
"summary": "Deleted the '2' switch statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
48
]
}
},
"summary": "Deleted the '1' switch statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
48
]
}
},
"summary": "Added the '2' switch statement"
}
]
},
"errors": {}
@ -84,16 +272,30 @@
"filePaths": [
"switch-statement.js"
],
"sha1": "c7325fbbeedf0a427a6ce87cd26cf8031ad9bd99",
"sha1": "f3d3fb5a9daeccf22d32dbcf79e3e6db7e00ac2e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ef998806acb4d21c1f65bb04b2090df5e757aa5b"
"sha2": "033f48b1db9de57690d1e8008aabb6435eb33732"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-test",
"expectedResult": {
"changes": {
"switch-statement.js": [
"Deleted the '1' switch statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
48
]
}
},
"summary": "Deleted the '1' switch statement"
}
]
},
"errors": {}
@ -101,16 +303,30 @@
"filePaths": [
"switch-statement.js"
],
"sha1": "ef998806acb4d21c1f65bb04b2090df5e757aa5b",
"sha1": "033f48b1db9de57690d1e8008aabb6435eb33732",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4413a2eb6b20759dedc9e8feeb5b384bec3781cc"
"sha2": "cf1d8915d86aa7b40cc64d3a1b48e4633a034465"
}
,{
"testCaseDescription": "javascript-switch-statement-delete-rest-test",
"expectedResult": {
"changes": {
"switch-statement.js": [
"Deleted the '2' switch statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
48
]
}
},
"summary": "Deleted the '2' switch statement"
}
]
},
"errors": {}
@ -118,7 +334,7 @@
"filePaths": [
"switch-statement.js"
],
"sha1": "4413a2eb6b20759dedc9e8feeb5b384bec3781cc",
"sha1": "cf1d8915d86aa7b40cc64d3a1b48e4633a034465",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a86d0e4d4e3bb52c63e6f75a4501457a20f3c1a1"
"sha2": "e34cec33423018aab0fa290f745d2dcb89c93f0f"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"template-string.js": [
"Added the '`one line`' template string"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Added the '`one line`' template string"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"template-string.js"
],
"sha1": "2177649d1d22edbb1ab004346f327e906b362e8d",
"sha1": "eac947afc7bc887c4b69523c4a6f77983a183edb",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0faea23b8b5807c1c07c83dc921b4ab988934d57"
"sha2": "950c2afcd03ac3b200b4f8b9a9aec3817648b04b"
}
,{
"testCaseDescription": "javascript-template-string-replacement-insert-test",
"expectedResult": {
"changes": {
"template-string.js": [
"Added the '`multi line`' template string",
"Added the '`one line`' template string"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the '`multi line`' template string"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
11
]
}
},
"summary": "Added the '`one line`' template string"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"template-string.js"
],
"sha1": "0faea23b8b5807c1c07c83dc921b4ab988934d57",
"sha1": "950c2afcd03ac3b200b4f8b9a9aec3817648b04b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "81f1e19a21bb54e9e5f61466f1a4c9a6774df5d9"
"sha2": "accc809e8ce1122d8b6151774c1fd769309c8e0f"
}
,{
"testCaseDescription": "javascript-template-string-delete-insert-test",
"expectedResult": {
"changes": {
"template-string.js": [
"Replaced the '`multi line`' template string with the '`one line`' template string"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
13
]
},
{
"start": [
1,
1
],
"end": [
1,
11
]
}
]
},
"summary": "Replaced the '`multi line`' template string with the '`one line`' template string"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"template-string.js"
],
"sha1": "81f1e19a21bb54e9e5f61466f1a4c9a6774df5d9",
"sha1": "accc809e8ce1122d8b6151774c1fd769309c8e0f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f0a908353187584dc340f0c8b5a555eaa7cead70"
"sha2": "8737d021e9a9a63b61b17a1a18feb0e56dd25833"
}
,{
"testCaseDescription": "javascript-template-string-replacement-test",
"expectedResult": {
"changes": {
"template-string.js": [
"Replaced the '`one line`' template string with the '`multi line`' template string"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
11
]
},
{
"start": [
1,
1
],
"end": [
1,
13
]
}
]
},
"summary": "Replaced the '`one line`' template string with the '`multi line`' template string"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"template-string.js"
],
"sha1": "f0a908353187584dc340f0c8b5a555eaa7cead70",
"sha1": "8737d021e9a9a63b61b17a1a18feb0e56dd25833",
"gitDir": "test/corpus/repos/javascript",
"sha2": "31c3c1e00886509ccc1cfea3a60fceb58d1d74a7"
"sha2": "7b2f1a9735c2c7e49481be1f7ca76a4d265adaa1"
}
,{
"testCaseDescription": "javascript-template-string-delete-replacement-test",
"expectedResult": {
"changes": {
"template-string.js": [
"Deleted the '`multi line`' template string",
"Deleted the '`one line`' template string",
"Added the '`multi line`' template string"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the '`multi line`' template string"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
11
]
}
},
"summary": "Deleted the '`one line`' template string"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Added the '`multi line`' template string"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"template-string.js"
],
"sha1": "31c3c1e00886509ccc1cfea3a60fceb58d1d74a7",
"sha1": "7b2f1a9735c2c7e49481be1f7ca76a4d265adaa1",
"gitDir": "test/corpus/repos/javascript",
"sha2": "19b8f088f4481875d69ec06eb89025d307b7d403"
"sha2": "897d45ce3ce2e3abebd4f6c51f50ed8f3677b3bd"
}
,{
"testCaseDescription": "javascript-template-string-delete-test",
"expectedResult": {
"changes": {
"template-string.js": [
"Deleted the '`one line`' template string"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
11
]
}
},
"summary": "Deleted the '`one line`' template string"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"template-string.js"
],
"sha1": "19b8f088f4481875d69ec06eb89025d307b7d403",
"sha1": "897d45ce3ce2e3abebd4f6c51f50ed8f3677b3bd",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9f29bb137ffecd8f1139b84dba66044098efebcc"
"sha2": "6fb06ea1442e30240106f1f36d59bd06ab2edb1f"
}
,{
"testCaseDescription": "javascript-template-string-delete-rest-test",
"expectedResult": {
"changes": {
"template-string.js": [
"Deleted the '`multi line`' template string"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the '`multi line`' template string"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"template-string.js"
],
"sha1": "9f29bb137ffecd8f1139b84dba66044098efebcc",
"sha1": "6fb06ea1442e30240106f1f36d59bd06ab2edb1f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d595e5cb7bd31790842877e1f7c6f8aee6e2b036"
"sha2": "8df53a54c07fb78bfcd4ee6537e27adcb642531f"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"ternary.js": [
"Added the 'condition' ternary expression"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
26
]
}
},
"summary": "Added the 'condition' ternary expression"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"ternary.js"
],
"sha1": "0b57e3c9e5f144a1cce790a12432819561d9d3d3",
"sha1": "b5446feffd11ca904e2726a11bbc705545843599",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f5efaa42bad7ca2cdde01ab615ab4798b4ee5be8"
"sha2": "4fbda1abcb8e30b6210e9bca5816014b7eff3407"
}
,{
"testCaseDescription": "javascript-ternary-replacement-insert-test",
"expectedResult": {
"changes": {
"ternary.js": [
"Added the 'x.y' assignment",
"Added the 'condition' ternary expression"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
51
]
}
},
"summary": "Added the 'x.y' assignment"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
26
]
}
},
"summary": "Added the 'condition' ternary expression"
}
]
},
"errors": {}
@ -29,17 +71,45 @@
"filePaths": [
"ternary.js"
],
"sha1": "f5efaa42bad7ca2cdde01ab615ab4798b4ee5be8",
"sha1": "4fbda1abcb8e30b6210e9bca5816014b7eff3407",
"gitDir": "test/corpus/repos/javascript",
"sha2": "cf05224706f16d817159a2a1f8879e952f4eea7b"
"sha2": "5a36618a7c9b673f065008726471679618abb60a"
}
,{
"testCaseDescription": "javascript-ternary-delete-insert-test",
"expectedResult": {
"changes": {
"ternary.js": [
"Added the 'condition' ternary expression",
"Deleted the 'x.y' assignment"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
26
]
}
},
"summary": "Added the 'condition' ternary expression"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
51
]
}
},
"summary": "Deleted the 'x.y' assignment"
}
]
},
"errors": {}
@ -47,17 +117,45 @@
"filePaths": [
"ternary.js"
],
"sha1": "cf05224706f16d817159a2a1f8879e952f4eea7b",
"sha1": "5a36618a7c9b673f065008726471679618abb60a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f5c9e30a15bdd3584010288ddc03d56250cca120"
"sha2": "7ac6d0565373cc2cf7e3aa3bdf51754c636b678d"
}
,{
"testCaseDescription": "javascript-ternary-replacement-test",
"expectedResult": {
"changes": {
"ternary.js": [
"Added the 'x.y' assignment",
"Deleted the 'condition' ternary expression"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
51
]
}
},
"summary": "Added the 'x.y' assignment"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
26
]
}
},
"summary": "Deleted the 'condition' ternary expression"
}
]
},
"errors": {}
@ -65,18 +163,60 @@
"filePaths": [
"ternary.js"
],
"sha1": "f5c9e30a15bdd3584010288ddc03d56250cca120",
"sha1": "7ac6d0565373cc2cf7e3aa3bdf51754c636b678d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "fbe27b1ffc5ac5e9af355ed01a212caa8a7e15ea"
"sha2": "90230dd8f3982615b5a2f7d9c96f7ebe6ef91a5a"
}
,{
"testCaseDescription": "javascript-ternary-delete-replacement-test",
"expectedResult": {
"changes": {
"ternary.js": [
"Deleted the 'x.y' assignment",
"Deleted the 'condition' ternary expression",
"Added the 'x.y' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
51
]
}
},
"summary": "Deleted the 'x.y' assignment"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
26
]
}
},
"summary": "Deleted the 'condition' ternary expression"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
51
]
}
},
"summary": "Added the 'x.y' assignment"
}
]
},
"errors": {}
@ -84,16 +224,30 @@
"filePaths": [
"ternary.js"
],
"sha1": "fbe27b1ffc5ac5e9af355ed01a212caa8a7e15ea",
"sha1": "90230dd8f3982615b5a2f7d9c96f7ebe6ef91a5a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7def2175d2590de16ad09041c44816612e9b7ec1"
"sha2": "7a926ee6d785e921b0253f556626ab7b2faa0d27"
}
,{
"testCaseDescription": "javascript-ternary-delete-test",
"expectedResult": {
"changes": {
"ternary.js": [
"Deleted the 'condition' ternary expression"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
26
]
}
},
"summary": "Deleted the 'condition' ternary expression"
}
]
},
"errors": {}
@ -101,16 +255,30 @@
"filePaths": [
"ternary.js"
],
"sha1": "7def2175d2590de16ad09041c44816612e9b7ec1",
"sha1": "7a926ee6d785e921b0253f556626ab7b2faa0d27",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2cd8b4a647361be100257e21017c12d9064e1d1f"
"sha2": "88c0457d70f6e468e3c6fc7ba3982a31c57d80dc"
}
,{
"testCaseDescription": "javascript-ternary-delete-rest-test",
"expectedResult": {
"changes": {
"ternary.js": [
"Deleted the 'x.y' assignment"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
51
]
}
},
"summary": "Deleted the 'x.y' assignment"
}
]
},
"errors": {}
@ -118,7 +286,7 @@
"filePaths": [
"ternary.js"
],
"sha1": "2cd8b4a647361be100257e21017c12d9064e1d1f",
"sha1": "88c0457d70f6e468e3c6fc7ba3982a31c57d80dc",
"gitDir": "test/corpus/repos/javascript",
"sha2": "c035407749e02f5dee9c3947118cd25095b28446"
"sha2": "9fd6bf4586ccb3910de1ff443d7928bce68977cb"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"this-expression.js": [
"Added the 'this' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Added the 'this' identifier"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"this-expression.js"
],
"sha1": "d04271adf62b579bffb014a03e4e401ce79164ea",
"sha1": "6a44e531842b97c2a60eb0fb38c57fe35035cf16",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e0d6ac03d62e39a1123e64f52cde9cbaf594a56b"
"sha2": "915f0a11edc274872a8147949183e8b07c9fad4b"
}
,{
"testCaseDescription": "javascript-this-expression-replacement-insert-test",
"expectedResult": {
"changes": {
"this-expression.js": [
"Added the 'this' return statement",
"Added the 'this' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'this' return statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
5
]
}
},
"summary": "Added the 'this' identifier"
}
]
},
"errors": {}
@ -29,17 +71,45 @@
"filePaths": [
"this-expression.js"
],
"sha1": "e0d6ac03d62e39a1123e64f52cde9cbaf594a56b",
"sha1": "915f0a11edc274872a8147949183e8b07c9fad4b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d7169b44d02f085007463a17ffa566abc2ded442"
"sha2": "adb919fd11be97d945483b00e4d2f37856e483b6"
}
,{
"testCaseDescription": "javascript-this-expression-delete-insert-test",
"expectedResult": {
"changes": {
"this-expression.js": [
"Added the 'this' identifier",
"Deleted the 'this' return statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Added the 'this' identifier"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'this' return statement"
}
]
},
"errors": {}
@ -47,17 +117,45 @@
"filePaths": [
"this-expression.js"
],
"sha1": "d7169b44d02f085007463a17ffa566abc2ded442",
"sha1": "adb919fd11be97d945483b00e4d2f37856e483b6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "1773f03cd2f7357d0ff1f29d14f233b1977d10b5"
"sha2": "877ee8b57e204cd9e3569f3adaad096ec8a970dd"
}
,{
"testCaseDescription": "javascript-this-expression-replacement-test",
"expectedResult": {
"changes": {
"this-expression.js": [
"Added the 'this' return statement",
"Deleted the 'this' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'this' return statement"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Deleted the 'this' identifier"
}
]
},
"errors": {}
@ -65,18 +163,60 @@
"filePaths": [
"this-expression.js"
],
"sha1": "1773f03cd2f7357d0ff1f29d14f233b1977d10b5",
"sha1": "877ee8b57e204cd9e3569f3adaad096ec8a970dd",
"gitDir": "test/corpus/repos/javascript",
"sha2": "04c2d41d544dfb57ddf56ab765b1a058f12521d4"
"sha2": "2a193071c5327473bc0e781d94e32a64495884eb"
}
,{
"testCaseDescription": "javascript-this-expression-delete-replacement-test",
"expectedResult": {
"changes": {
"this-expression.js": [
"Deleted the 'this' return statement",
"Deleted the 'this' identifier",
"Added the 'this' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'this' return statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
5
]
}
},
"summary": "Deleted the 'this' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Added the 'this' return statement"
}
]
},
"errors": {}
@ -84,16 +224,30 @@
"filePaths": [
"this-expression.js"
],
"sha1": "04c2d41d544dfb57ddf56ab765b1a058f12521d4",
"sha1": "2a193071c5327473bc0e781d94e32a64495884eb",
"gitDir": "test/corpus/repos/javascript",
"sha2": "db6d5182417a36293409dd9cc6cf21c87c5126db"
"sha2": "916921ca606d1206fa980e030ed31cd87966e946"
}
,{
"testCaseDescription": "javascript-this-expression-delete-test",
"expectedResult": {
"changes": {
"this-expression.js": [
"Deleted the 'this' identifier"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Deleted the 'this' identifier"
}
]
},
"errors": {}
@ -101,16 +255,30 @@
"filePaths": [
"this-expression.js"
],
"sha1": "db6d5182417a36293409dd9cc6cf21c87c5126db",
"sha1": "916921ca606d1206fa980e030ed31cd87966e946",
"gitDir": "test/corpus/repos/javascript",
"sha2": "3e99956fce21f55e966c36997b3549013365945b"
"sha2": "ccf1e1fa57208cdefeb650390c4153ba13d60b23"
}
,{
"testCaseDescription": "javascript-this-expression-delete-rest-test",
"expectedResult": {
"changes": {
"this-expression.js": [
"Deleted the 'this' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'this' return statement"
}
]
},
"errors": {}
@ -118,7 +286,7 @@
"filePaths": [
"this-expression.js"
],
"sha1": "3e99956fce21f55e966c36997b3549013365945b",
"sha1": "ccf1e1fa57208cdefeb650390c4153ba13d60b23",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a089d3a69cf2a56aa770c7f9446691ddd6edfac2"
"sha2": "027732543c3974844a2f660a3ee74c0837a5b055"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"throw-statement.js": [
"Added the 'new Error(\"uh oh\")' throw statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
26
]
}
},
"summary": "Added the 'new Error(\"uh oh\")' throw statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"throw-statement.js"
],
"sha1": "a86d0e4d4e3bb52c63e6f75a4501457a20f3c1a1",
"sha1": "04ac626daa098bf596f572115ce36f8cf31b84df",
"gitDir": "test/corpus/repos/javascript",
"sha2": "176cbd788804f39e78b66dcd91ad46fc5f2e8228"
"sha2": "6504a2a9d3f565d5812bbd79e02f53609761fe92"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
29
]
}
},
"summary": "Added the 'new Error(\"oooooops\")' throw statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
26
]
}
},
"summary": "Added the 'new Error(\"uh oh\")' throw statement"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"throw-statement.js"
],
"sha1": "176cbd788804f39e78b66dcd91ad46fc5f2e8228",
"sha1": "6504a2a9d3f565d5812bbd79e02f53609761fe92",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d7901e8a9c7bb031bd74f65627f9c7af19476d12"
"sha2": "5ea11da0cbfa31b113fe4c0c26a1949a6a2d12bd"
}
,{
"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"
{
"span": {
"replace": [
{
"start": [
1,
17
],
"end": [
1,
27
]
},
{
"start": [
1,
17
],
"end": [
1,
24
]
}
]
},
"summary": "Replaced the \"oooooops\" string with the \"uh oh\" string in the Error(\"uh oh\") function call"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"throw-statement.js"
],
"sha1": "d7901e8a9c7bb031bd74f65627f9c7af19476d12",
"sha1": "5ea11da0cbfa31b113fe4c0c26a1949a6a2d12bd",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6edfd5e59f539bb0b5b4a5b8beafe213a8bc093a"
"sha2": "47633d9af7926f59a4a8555688683cc43c055266"
}
,{
"testCaseDescription": "javascript-throw-statement-replacement-test",
"expectedResult": {
"changes": {
"throw-statement.js": [
"Replaced the \"uh oh\" string with the \"oooooops\" string in the Error(\"oooooops\") function call"
{
"span": {
"replace": [
{
"start": [
1,
17
],
"end": [
1,
24
]
},
{
"start": [
1,
17
],
"end": [
1,
27
]
}
]
},
"summary": "Replaced the \"uh oh\" string with the \"oooooops\" string in the Error(\"oooooops\") function call"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"throw-statement.js"
],
"sha1": "6edfd5e59f539bb0b5b4a5b8beafe213a8bc093a",
"sha1": "47633d9af7926f59a4a8555688683cc43c055266",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7010a5625bed7789454ae7ced5bf176463a3b269"
"sha2": "4e39f432c9e0d8a9f126b91f7ea54d21822c7c04"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-replacement-test",
"expectedResult": {
"changes": {
"throw-statement.js": [
"Deleted the 'new Error(\"oooooops\")' throw statement",
"Deleted the 'new Error(\"uh oh\")' throw statement",
"Added the 'new Error(\"oooooops\")' throw statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
29
]
}
},
"summary": "Deleted the 'new Error(\"oooooops\")' throw statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
26
]
}
},
"summary": "Deleted the 'new Error(\"uh oh\")' throw statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
29
]
}
},
"summary": "Added the 'new Error(\"oooooops\")' throw statement"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"throw-statement.js"
],
"sha1": "7010a5625bed7789454ae7ced5bf176463a3b269",
"sha1": "4e39f432c9e0d8a9f126b91f7ea54d21822c7c04",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e5b90c94af0940d8772e800672a2a7b7b9000b26"
"sha2": "09ebd0d64a6252d651e35cf07c181750d7b1da40"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-test",
"expectedResult": {
"changes": {
"throw-statement.js": [
"Deleted the 'new Error(\"uh oh\")' throw statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
26
]
}
},
"summary": "Deleted the 'new Error(\"uh oh\")' throw statement"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"throw-statement.js"
],
"sha1": "e5b90c94af0940d8772e800672a2a7b7b9000b26",
"sha1": "09ebd0d64a6252d651e35cf07c181750d7b1da40",
"gitDir": "test/corpus/repos/javascript",
"sha2": "897c91c3a049d9f5d30b14653969d7b30aebb132"
"sha2": "4da8a2dd13d1b62a139f102cf2d13ce0cf6f3bb7"
}
,{
"testCaseDescription": "javascript-throw-statement-delete-rest-test",
"expectedResult": {
"changes": {
"throw-statement.js": [
"Deleted the 'new Error(\"oooooops\")' throw statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
29
]
}
},
"summary": "Deleted the 'new Error(\"oooooops\")' throw statement"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"throw-statement.js"
],
"sha1": "897c91c3a049d9f5d30b14653969d7b30aebb132",
"sha1": "4da8a2dd13d1b62a139f102cf2d13ce0cf6f3bb7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "bda19093cbfbd4a0e1242d45140912e077e0f04f"
"sha2": "5c30863954c846e6487626965891f282d42e6b84"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"true.js": [
"Added 'true'"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Added 'true'"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"true.js"
],
"sha1": "ff66f0bede75bdabc3e3ad7807372250e9e3b0cd",
"sha1": "f6baf27a65896e7e502d6ec646cb3cbbd7e206f6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e1ec29466e4e5ac0aabb6c68d42d0a1930a66053"
"sha2": "5091492afacae27e07b10a11965b4b5338f092c8"
}
,{
"testCaseDescription": "javascript-true-replacement-insert-test",
"expectedResult": {
"changes": {
"true.js": [
"Added the 'true' return statement",
"Added 'true'"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'true' return statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
5
]
}
},
"summary": "Added 'true'"
}
]
},
"errors": {}
@ -29,17 +71,45 @@
"filePaths": [
"true.js"
],
"sha1": "e1ec29466e4e5ac0aabb6c68d42d0a1930a66053",
"sha1": "5091492afacae27e07b10a11965b4b5338f092c8",
"gitDir": "test/corpus/repos/javascript",
"sha2": "e97097a80f5b117e571f2ecd2f5eb373a8e11f3f"
"sha2": "3bbd68f2e51402ce75780e5af72c03512991d95b"
}
,{
"testCaseDescription": "javascript-true-delete-insert-test",
"expectedResult": {
"changes": {
"true.js": [
"Added 'true'",
"Deleted the 'true' return statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Added 'true'"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'true' return statement"
}
]
},
"errors": {}
@ -47,17 +117,45 @@
"filePaths": [
"true.js"
],
"sha1": "e97097a80f5b117e571f2ecd2f5eb373a8e11f3f",
"sha1": "3bbd68f2e51402ce75780e5af72c03512991d95b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5d054d6442dc613ed3a78428fd1146b8096dd7fe"
"sha2": "12760109620d0e2aebc964bf10793a9018a7a993"
}
,{
"testCaseDescription": "javascript-true-replacement-test",
"expectedResult": {
"changes": {
"true.js": [
"Added the 'true' return statement",
"Deleted 'true'"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Added the 'true' return statement"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Deleted 'true'"
}
]
},
"errors": {}
@ -65,18 +163,60 @@
"filePaths": [
"true.js"
],
"sha1": "5d054d6442dc613ed3a78428fd1146b8096dd7fe",
"sha1": "12760109620d0e2aebc964bf10793a9018a7a993",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a9dd88db5f08097ce3659a4f994f9755cba7c7cc"
"sha2": "6b269c9b079a987453884c3d4f894bfb4e76be70"
}
,{
"testCaseDescription": "javascript-true-delete-replacement-test",
"expectedResult": {
"changes": {
"true.js": [
"Deleted the 'true' return statement",
"Deleted 'true'",
"Added the 'true' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'true' return statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
5
]
}
},
"summary": "Deleted 'true'"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
13
]
}
},
"summary": "Added the 'true' return statement"
}
]
},
"errors": {}
@ -84,16 +224,30 @@
"filePaths": [
"true.js"
],
"sha1": "a9dd88db5f08097ce3659a4f994f9755cba7c7cc",
"sha1": "6b269c9b079a987453884c3d4f894bfb4e76be70",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6496eb970d565277cd61bb6bf0f6786e8b96c2d8"
"sha2": "0fe461d1797041345efd7168414a5d143c47a0b8"
}
,{
"testCaseDescription": "javascript-true-delete-test",
"expectedResult": {
"changes": {
"true.js": [
"Deleted 'true'"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
5
]
}
},
"summary": "Deleted 'true'"
}
]
},
"errors": {}
@ -101,16 +255,30 @@
"filePaths": [
"true.js"
],
"sha1": "6496eb970d565277cd61bb6bf0f6786e8b96c2d8",
"sha1": "0fe461d1797041345efd7168414a5d143c47a0b8",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7bb5eb030fd5013a2c0a4a3a2167023548310739"
"sha2": "f6239893bd02de6e0a7e7f5ef678ad2421d0719e"
}
,{
"testCaseDescription": "javascript-true-delete-rest-test",
"expectedResult": {
"changes": {
"true.js": [
"Deleted the 'true' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
13
]
}
},
"summary": "Deleted the 'true' return statement"
}
]
},
"errors": {}
@ -118,7 +286,7 @@
"filePaths": [
"true.js"
],
"sha1": "7bb5eb030fd5013a2c0a4a3a2167023548310739",
"sha1": "f6239893bd02de6e0a7e7f5ef678ad2421d0719e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b8860daa68624499e345ce91a8701d70785b2d4e"
"sha2": "b5f63d0fc82f7a027e684d209d08915d0b2bf95c"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"try-statement.js": [
"Added the '{ f; }' try statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
39
]
}
},
"summary": "Added the '{ f; }' try statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"try-statement.js"
],
"sha1": "bda19093cbfbd4a0e1242d45140912e077e0f04f",
"sha1": "b908a6724f0ad01f8801ea57866f313307e6b319",
"gitDir": "test/corpus/repos/javascript",
"sha2": "86c53d76fc1eb653a845a58c41ab861355432d4e"
"sha2": "d3adba31d9e7e79d07e703ad2a6967562b220f6b"
}
,{
"testCaseDescription": "javascript-try-statement-replacement-insert-test",
"expectedResult": {
"changes": {
"try-statement.js": [
"Added the '{ f; }' try statement",
"Added the '{ f; }' try statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
39
]
}
},
"summary": "Added the '{ f; }' try statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
39
]
}
},
"summary": "Added the '{ f; }' try statement"
}
]
},
"errors": {}
@ -29,17 +71,69 @@
"filePaths": [
"try-statement.js"
],
"sha1": "86c53d76fc1eb653a845a58c41ab861355432d4e",
"sha1": "d3adba31d9e7e79d07e703ad2a6967562b220f6b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9764b94d36b0c923758fbf9c65b2053c38720f10"
"sha2": "c1fc74cb0f5db63aee48f72adcd8abccccbc931c"
}
,{
"testCaseDescription": "javascript-try-statement-delete-insert-test",
"expectedResult": {
"changes": {
"try-statement.js": [
"Replaced the 'h' identifier with the 'g' identifier",
"Replaced the 'g' identifier with the 'h' identifier"
{
"span": {
"replace": [
{
"start": [
1,
20
],
"end": [
1,
21
]
},
{
"start": [
1,
20
],
"end": [
1,
21
]
}
]
},
"summary": "Replaced the 'h' identifier with the 'g' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
35
],
"end": [
1,
36
]
},
{
"start": [
1,
35
],
"end": [
1,
36
]
}
]
},
"summary": "Replaced the 'g' identifier with the 'h' identifier"
}
]
},
"errors": {}
@ -47,17 +141,69 @@
"filePaths": [
"try-statement.js"
],
"sha1": "9764b94d36b0c923758fbf9c65b2053c38720f10",
"sha1": "c1fc74cb0f5db63aee48f72adcd8abccccbc931c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "004b6b18d206a498cf2d0674b0eae1b51b5fa25e"
"sha2": "18a5e0f40787e268714e8c7bd3e1641d76d78319"
}
,{
"testCaseDescription": "javascript-try-statement-replacement-test",
"expectedResult": {
"changes": {
"try-statement.js": [
"Replaced the 'g' identifier with the 'h' identifier",
"Replaced the 'h' identifier with the 'g' identifier"
{
"span": {
"replace": [
{
"start": [
1,
20
],
"end": [
1,
21
]
},
{
"start": [
1,
20
],
"end": [
1,
21
]
}
]
},
"summary": "Replaced the 'g' identifier with the 'h' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
35
],
"end": [
1,
36
]
},
{
"start": [
1,
35
],
"end": [
1,
36
]
}
]
},
"summary": "Replaced the 'h' identifier with the 'g' identifier"
}
]
},
"errors": {}
@ -65,18 +211,60 @@
"filePaths": [
"try-statement.js"
],
"sha1": "004b6b18d206a498cf2d0674b0eae1b51b5fa25e",
"sha1": "18a5e0f40787e268714e8c7bd3e1641d76d78319",
"gitDir": "test/corpus/repos/javascript",
"sha2": "fa1495981b727cc3c08e04dcaf8529fcd51fc640"
"sha2": "f836874a0d43f61e721d253cf3f97fd0a83cb6e7"
}
,{
"testCaseDescription": "javascript-try-statement-delete-replacement-test",
"expectedResult": {
"changes": {
"try-statement.js": [
"Deleted the '{ f; }' try statement",
"Deleted the '{ f; }' try statement",
"Added the '{ f; }' try statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
39
]
}
},
"summary": "Deleted the '{ f; }' try statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
39
]
}
},
"summary": "Deleted the '{ f; }' try statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
39
]
}
},
"summary": "Added the '{ f; }' try statement"
}
]
},
"errors": {}
@ -84,16 +272,30 @@
"filePaths": [
"try-statement.js"
],
"sha1": "fa1495981b727cc3c08e04dcaf8529fcd51fc640",
"sha1": "f836874a0d43f61e721d253cf3f97fd0a83cb6e7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d61df50c596b96e0c7bd2c0b49d5c737c10ba62d"
"sha2": "8776c024182abad3bb3f5f68e999e1172fd0bce0"
}
,{
"testCaseDescription": "javascript-try-statement-delete-test",
"expectedResult": {
"changes": {
"try-statement.js": [
"Deleted the '{ f; }' try statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
39
]
}
},
"summary": "Deleted the '{ f; }' try statement"
}
]
},
"errors": {}
@ -101,16 +303,30 @@
"filePaths": [
"try-statement.js"
],
"sha1": "d61df50c596b96e0c7bd2c0b49d5c737c10ba62d",
"sha1": "8776c024182abad3bb3f5f68e999e1172fd0bce0",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7cc0d5231bea02484b0dfe21caeb93be7f2106a9"
"sha2": "fb43fddce814a12e5f3a96d13a6a533ea965218c"
}
,{
"testCaseDescription": "javascript-try-statement-delete-rest-test",
"expectedResult": {
"changes": {
"try-statement.js": [
"Deleted the '{ f; }' try statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
39
]
}
},
"summary": "Deleted the '{ f; }' try statement"
}
]
},
"errors": {}
@ -118,7 +334,7 @@
"filePaths": [
"try-statement.js"
],
"sha1": "7cc0d5231bea02484b0dfe21caeb93be7f2106a9",
"sha1": "fb43fddce814a12e5f3a96d13a6a533ea965218c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0c5416c3cc4fe3d23080c580f0a962802b756bac"
"sha2": "f03ea63f2c081eb44cc3094034c2320fa50f8520"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"type-operator.js": [
"Added the 'typeof x' operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
9
]
}
},
"summary": "Added the 'typeof x' operator"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"type-operator.js"
],
"sha1": "c035407749e02f5dee9c3947118cd25095b28446",
"sha1": "6eeb048dd356c28a76842bafe0ff471aca4fc709",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ba4599ba8153ddf393c28166e5c3682ca695c3c0"
"sha2": "ae302058d381bfe2242f8af75707d16d9bc5f9c6"
}
,{
"testCaseDescription": "javascript-type-operator-replacement-insert-test",
"expectedResult": {
"changes": {
"type-operator.js": [
"Added the 'x instanceof String' operator",
"Added the 'typeof x' operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Added the 'x instanceof String' operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Added the 'typeof x' operator"
}
]
},
"errors": {}
@ -29,16 +71,30 @@
"filePaths": [
"type-operator.js"
],
"sha1": "ba4599ba8153ddf393c28166e5c3682ca695c3c0",
"sha1": "ae302058d381bfe2242f8af75707d16d9bc5f9c6",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a6b0e4e444389879aca8497b3f91ae9b5a8d8db9"
"sha2": "70ff969d615bb1e12f9c83a34430c4eecf5e1423"
}
,{
"testCaseDescription": "javascript-type-operator-delete-insert-test",
"expectedResult": {
"changes": {
"type-operator.js": [
"Deleted the 'String' identifier"
{
"span": {
"delete": {
"start": [
1,
14
],
"end": [
1,
20
]
}
},
"summary": "Deleted the 'String' identifier"
}
]
},
"errors": {}
@ -46,16 +102,30 @@
"filePaths": [
"type-operator.js"
],
"sha1": "a6b0e4e444389879aca8497b3f91ae9b5a8d8db9",
"sha1": "70ff969d615bb1e12f9c83a34430c4eecf5e1423",
"gitDir": "test/corpus/repos/javascript",
"sha2": "68e72b46ca8515ca2d89106454d244f13498d6a7"
"sha2": "4e7d94a429cfea4cfb43bee17420bdf2cf31857e"
}
,{
"testCaseDescription": "javascript-type-operator-replacement-test",
"expectedResult": {
"changes": {
"type-operator.js": [
"Added the 'String' identifier"
{
"span": {
"insert": {
"start": [
1,
14
],
"end": [
1,
20
]
}
},
"summary": "Added the 'String' identifier"
}
]
},
"errors": {}
@ -63,18 +133,60 @@
"filePaths": [
"type-operator.js"
],
"sha1": "68e72b46ca8515ca2d89106454d244f13498d6a7",
"sha1": "4e7d94a429cfea4cfb43bee17420bdf2cf31857e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "033e0f3408966f10835fe6e9b288161f66ce04cc"
"sha2": "5f0e7b153777bb043786fa66aee9e38978d66762"
}
,{
"testCaseDescription": "javascript-type-operator-delete-replacement-test",
"expectedResult": {
"changes": {
"type-operator.js": [
"Deleted the 'x instanceof String' operator",
"Deleted the 'typeof x' operator",
"Added the 'x instanceof String' operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Deleted the 'x instanceof String' operator"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Deleted the 'typeof x' operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
20
]
}
},
"summary": "Added the 'x instanceof String' operator"
}
]
},
"errors": {}
@ -82,16 +194,30 @@
"filePaths": [
"type-operator.js"
],
"sha1": "033e0f3408966f10835fe6e9b288161f66ce04cc",
"sha1": "5f0e7b153777bb043786fa66aee9e38978d66762",
"gitDir": "test/corpus/repos/javascript",
"sha2": "703588929b2883da6546fb1fe911ec45f9445aa7"
"sha2": "9aaacd568854471edc874364923b43b5a65f6caf"
}
,{
"testCaseDescription": "javascript-type-operator-delete-test",
"expectedResult": {
"changes": {
"type-operator.js": [
"Deleted the 'typeof x' operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
9
]
}
},
"summary": "Deleted the 'typeof x' operator"
}
]
},
"errors": {}
@ -99,16 +225,30 @@
"filePaths": [
"type-operator.js"
],
"sha1": "703588929b2883da6546fb1fe911ec45f9445aa7",
"sha1": "9aaacd568854471edc874364923b43b5a65f6caf",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5a0bb75f3ce6baba9ecc2516deaa8a515c7f422d"
"sha2": "b91ec6770bb9eed6aa7f9a0b24c65d6460ba825d"
}
,{
"testCaseDescription": "javascript-type-operator-delete-rest-test",
"expectedResult": {
"changes": {
"type-operator.js": [
"Deleted the 'x instanceof String' operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
20
]
}
},
"summary": "Deleted the 'x instanceof String' operator"
}
]
},
"errors": {}
@ -116,7 +256,7 @@
"filePaths": [
"type-operator.js"
],
"sha1": "5a0bb75f3ce6baba9ecc2516deaa8a515c7f422d",
"sha1": "b91ec6770bb9eed6aa7f9a0b24c65d6460ba825d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "29bb6e3625ec9c3bbd58c6ba514d9f7ebce67705"
"sha2": "1d96325511c74b433e0a9c675a1e9c1a368bf222"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"undefined.js": [
"Added the 'undefined' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
10
]
}
},
"summary": "Added the 'undefined' identifier"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"undefined.js"
],
"sha1": "baaf540faedf1f9d3d4dbb4da81b68f94cdd18f4",
"sha1": "49e91b55ab4d34df9d10e18a357ecb3f9129d38b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d6944b827c9a5c7ec7a99b3ba46c1b323a3790a2"
"sha2": "670251c94df41dfcbe8b26ad37cf7b723051a348"
}
,{
"testCaseDescription": "javascript-undefined-replacement-insert-test",
"expectedResult": {
"changes": {
"undefined.js": [
"Added the 'undefined' return statement",
"Added the 'undefined' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Added the 'undefined' return statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
10
]
}
},
"summary": "Added the 'undefined' identifier"
}
]
},
"errors": {}
@ -29,17 +71,45 @@
"filePaths": [
"undefined.js"
],
"sha1": "d6944b827c9a5c7ec7a99b3ba46c1b323a3790a2",
"sha1": "670251c94df41dfcbe8b26ad37cf7b723051a348",
"gitDir": "test/corpus/repos/javascript",
"sha2": "1fbafb7edf193695180b57521515132552a16ae7"
"sha2": "1cc3532b64f1b7f19e3676f8625a2b12cfe2630b"
}
,{
"testCaseDescription": "javascript-undefined-delete-insert-test",
"expectedResult": {
"changes": {
"undefined.js": [
"Added the 'undefined' identifier",
"Deleted the 'undefined' return statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
10
]
}
},
"summary": "Added the 'undefined' identifier"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the 'undefined' return statement"
}
]
},
"errors": {}
@ -47,17 +117,45 @@
"filePaths": [
"undefined.js"
],
"sha1": "1fbafb7edf193695180b57521515132552a16ae7",
"sha1": "1cc3532b64f1b7f19e3676f8625a2b12cfe2630b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "cdf0640740c3c3c3c202ac2fc66ba030edbacc0f"
"sha2": "db10576ffb9656dcaaba5532089eb76acf5d489f"
}
,{
"testCaseDescription": "javascript-undefined-replacement-test",
"expectedResult": {
"changes": {
"undefined.js": [
"Added the 'undefined' return statement",
"Deleted the 'undefined' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Added the 'undefined' return statement"
},
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
10
]
}
},
"summary": "Deleted the 'undefined' identifier"
}
]
},
"errors": {}
@ -65,18 +163,60 @@
"filePaths": [
"undefined.js"
],
"sha1": "cdf0640740c3c3c3c202ac2fc66ba030edbacc0f",
"sha1": "db10576ffb9656dcaaba5532089eb76acf5d489f",
"gitDir": "test/corpus/repos/javascript",
"sha2": "23946667babba7393dcc8f0b84f0cc316714c3ef"
"sha2": "fd6f48b2d37f71c4e9155b4fe875371543a92961"
}
,{
"testCaseDescription": "javascript-undefined-delete-replacement-test",
"expectedResult": {
"changes": {
"undefined.js": [
"Deleted the 'undefined' return statement",
"Deleted the 'undefined' identifier",
"Added the 'undefined' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the 'undefined' return statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
10
]
}
},
"summary": "Deleted the 'undefined' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
18
]
}
},
"summary": "Added the 'undefined' return statement"
}
]
},
"errors": {}
@ -84,16 +224,30 @@
"filePaths": [
"undefined.js"
],
"sha1": "23946667babba7393dcc8f0b84f0cc316714c3ef",
"sha1": "fd6f48b2d37f71c4e9155b4fe875371543a92961",
"gitDir": "test/corpus/repos/javascript",
"sha2": "873d1fe58b7e0a39802f5df4b889adc5b45c04a6"
"sha2": "5a182f3d30775c47d619dea99fb6912f14460f86"
}
,{
"testCaseDescription": "javascript-undefined-delete-test",
"expectedResult": {
"changes": {
"undefined.js": [
"Deleted the 'undefined' identifier"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
10
]
}
},
"summary": "Deleted the 'undefined' identifier"
}
]
},
"errors": {}
@ -101,16 +255,30 @@
"filePaths": [
"undefined.js"
],
"sha1": "873d1fe58b7e0a39802f5df4b889adc5b45c04a6",
"sha1": "5a182f3d30775c47d619dea99fb6912f14460f86",
"gitDir": "test/corpus/repos/javascript",
"sha2": "60cce6f9caed2462e19f406e7dc97477e7cca794"
"sha2": "58439f1bf80a8b82fae2f08eb8bfc1d1a96c4a7e"
}
,{
"testCaseDescription": "javascript-undefined-delete-rest-test",
"expectedResult": {
"changes": {
"undefined.js": [
"Deleted the 'undefined' return statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
18
]
}
},
"summary": "Deleted the 'undefined' return statement"
}
]
},
"errors": {}
@ -118,7 +286,7 @@
"filePaths": [
"undefined.js"
],
"sha1": "60cce6f9caed2462e19f406e7dc97477e7cca794",
"sha1": "58439f1bf80a8b82fae2f08eb8bfc1d1a96c4a7e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "ff66f0bede75bdabc3e3ad7807372250e9e3b0cd"
"sha2": "a36b31965536bd78704978e111fd017722054b27"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"var-declaration.js": [
"Added the 'x' variable"
{
"span": {
"insert": {
"start": [
1,
5
],
"end": [
1,
10
]
}
},
"summary": "Added the 'x' variable"
}
]
},
"errors": {}
@ -11,19 +25,75 @@
"filePaths": [
"var-declaration.js"
],
"sha1": "1331b0dc40147173385ee65a3f7a2a1b390bd6dd",
"sha1": "6f8397f676d372fb7cc681c6170eab3f00a5508b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "8c5160816d49b2f7f0f80e6ce578d5af724cb8ca"
"sha2": "a0b5c84fbb211d943917ca1b033d0f4d69e99fab"
}
,{
"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"
{
"span": {
"insert": {
"start": [
1,
5
],
"end": [
1,
6
]
}
},
"summary": "Added the 'x' variable"
},
{
"span": {
"insert": {
"start": [
1,
8
],
"end": [
1,
14
]
}
},
"summary": "Added the 'y' variable"
},
{
"span": {
"insert": {
"start": [
1,
16
],
"end": [
1,
17
]
}
},
"summary": "Added the 'z' variable"
},
{
"span": {
"insert": {
"start": [
2,
5
],
"end": [
2,
10
]
}
},
"summary": "Added the 'x' variable"
}
]
},
"errors": {}
@ -31,18 +101,72 @@
"filePaths": [
"var-declaration.js"
],
"sha1": "8c5160816d49b2f7f0f80e6ce578d5af724cb8ca",
"sha1": "a0b5c84fbb211d943917ca1b033d0f4d69e99fab",
"gitDir": "test/corpus/repos/javascript",
"sha2": "6543c8455d53d6569bf4dbf4f336cd6444854ce2"
"sha2": "b29aa1c8b4ce011908b5fcb146722a7415615b61"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-insert-test",
"expectedResult": {
"changes": {
"var-declaration.js": [
"Replaced the 'x' variable with the 'x' variable",
"Deleted the 'y' variable",
"Deleted the 'z' variable"
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
6
]
},
{
"start": [
1,
5
],
"end": [
1,
10
]
}
]
},
"summary": "Replaced the 'x' variable with the 'x' variable"
},
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
14
]
}
},
"summary": "Deleted the 'y' variable"
},
{
"span": {
"delete": {
"start": [
1,
16
],
"end": [
1,
17
]
}
},
"summary": "Deleted the 'z' variable"
}
]
},
"errors": {}
@ -50,18 +174,72 @@
"filePaths": [
"var-declaration.js"
],
"sha1": "6543c8455d53d6569bf4dbf4f336cd6444854ce2",
"sha1": "b29aa1c8b4ce011908b5fcb146722a7415615b61",
"gitDir": "test/corpus/repos/javascript",
"sha2": "d010d829a79bcaee125b1fae42092d69477e6e3e"
"sha2": "121898865a4153fdee7af490b7f95e63dfecd245"
}
,{
"testCaseDescription": "javascript-var-declaration-replacement-test",
"expectedResult": {
"changes": {
"var-declaration.js": [
"Replaced the 'x' variable with the 'x' variable",
"Added the 'y' variable",
"Added the 'z' variable"
{
"span": {
"replace": [
{
"start": [
1,
5
],
"end": [
1,
10
]
},
{
"start": [
1,
5
],
"end": [
1,
6
]
}
]
},
"summary": "Replaced the 'x' variable with the 'x' variable"
},
{
"span": {
"insert": {
"start": [
1,
8
],
"end": [
1,
14
]
}
},
"summary": "Added the 'y' variable"
},
{
"span": {
"insert": {
"start": [
1,
16
],
"end": [
1,
17
]
}
},
"summary": "Added the 'z' variable"
}
]
},
"errors": {}
@ -69,22 +247,120 @@
"filePaths": [
"var-declaration.js"
],
"sha1": "d010d829a79bcaee125b1fae42092d69477e6e3e",
"sha1": "121898865a4153fdee7af490b7f95e63dfecd245",
"gitDir": "test/corpus/repos/javascript",
"sha2": "82cdfb2674b148d8c442fd85988c5af99dd5f5d2"
"sha2": "4f800595767d306adf1001a3e532c0f49c77549b"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-replacement-test",
"expectedResult": {
"changes": {
"var-declaration.js": [
"Deleted the 'x' variable",
"Deleted the 'y' variable",
"Deleted the 'z' variable",
"Deleted the 'x' variable",
"Added the 'x' variable",
"Added the 'y' variable",
"Added the 'z' variable"
{
"span": {
"delete": {
"start": [
1,
5
],
"end": [
1,
6
]
}
},
"summary": "Deleted the 'x' variable"
},
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
14
]
}
},
"summary": "Deleted the 'y' variable"
},
{
"span": {
"delete": {
"start": [
1,
16
],
"end": [
1,
17
]
}
},
"summary": "Deleted the 'z' variable"
},
{
"span": {
"delete": {
"start": [
2,
5
],
"end": [
2,
10
]
}
},
"summary": "Deleted the 'x' variable"
},
{
"span": {
"insert": {
"start": [
2,
5
],
"end": [
2,
6
]
}
},
"summary": "Added the 'x' variable"
},
{
"span": {
"insert": {
"start": [
2,
8
],
"end": [
2,
14
]
}
},
"summary": "Added the 'y' variable"
},
{
"span": {
"insert": {
"start": [
2,
16
],
"end": [
2,
17
]
}
},
"summary": "Added the 'z' variable"
}
]
},
"errors": {}
@ -92,16 +368,30 @@
"filePaths": [
"var-declaration.js"
],
"sha1": "82cdfb2674b148d8c442fd85988c5af99dd5f5d2",
"sha1": "4f800595767d306adf1001a3e532c0f49c77549b",
"gitDir": "test/corpus/repos/javascript",
"sha2": "fb37223edafc9524e966cb3c9d4eca5a323d98ce"
"sha2": "a62c5f0ceea3f103315aab7f595f0fc257690f46"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-test",
"expectedResult": {
"changes": {
"var-declaration.js": [
"Deleted the 'x' variable"
{
"span": {
"delete": {
"start": [
1,
5
],
"end": [
1,
10
]
}
},
"summary": "Deleted the 'x' variable"
}
]
},
"errors": {}
@ -109,18 +399,60 @@
"filePaths": [
"var-declaration.js"
],
"sha1": "fb37223edafc9524e966cb3c9d4eca5a323d98ce",
"sha1": "a62c5f0ceea3f103315aab7f595f0fc257690f46",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4c89f395fad883f84c02b4041b2cfcbba14f5c9c"
"sha2": "a1ce7a96169c9034dbc16807e754c5a58df0c0f8"
}
,{
"testCaseDescription": "javascript-var-declaration-delete-rest-test",
"expectedResult": {
"changes": {
"var-declaration.js": [
"Deleted the 'x' variable",
"Deleted the 'y' variable",
"Deleted the 'z' variable"
{
"span": {
"delete": {
"start": [
1,
5
],
"end": [
1,
6
]
}
},
"summary": "Deleted the 'x' variable"
},
{
"span": {
"delete": {
"start": [
1,
8
],
"end": [
1,
14
]
}
},
"summary": "Deleted the 'y' variable"
},
{
"span": {
"delete": {
"start": [
1,
16
],
"end": [
1,
17
]
}
},
"summary": "Deleted the 'z' variable"
}
]
},
"errors": {}
@ -128,7 +460,7 @@
"filePaths": [
"var-declaration.js"
],
"sha1": "4c89f395fad883f84c02b4041b2cfcbba14f5c9c",
"sha1": "a1ce7a96169c9034dbc16807e754c5a58df0c0f8",
"gitDir": "test/corpus/repos/javascript",
"sha2": "fea1acf23c86b8d52dd9658d77c6478c2f1113a3"
"sha2": "538d0fcee9f9f1163338901d5c7ec3035da370c4"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"variable.js": [
"Added the 'theVar' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Added the 'theVar' identifier"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"variable.js"
],
"sha1": "ff7982a5abb0149fc5cd9e70597748c467270bbc",
"sha1": "af7fa2faefa291b9a06977c18ce312bffe7bc871",
"gitDir": "test/corpus/repos/javascript",
"sha2": "9cabecdfc59bf4196571840d6698d408c44a310a"
"sha2": "60d7f50440d1afcabab62927fc575f4aa29cbac7"
}
,{
"testCaseDescription": "javascript-variable-replacement-insert-test",
"expectedResult": {
"changes": {
"variable.js": [
"Added the 'theVar2' identifier",
"Added the 'theVar' identifier"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Added the 'theVar2' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Added the 'theVar' identifier"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"variable.js"
],
"sha1": "9cabecdfc59bf4196571840d6698d408c44a310a",
"sha1": "60d7f50440d1afcabab62927fc575f4aa29cbac7",
"gitDir": "test/corpus/repos/javascript",
"sha2": "0930920535116a7d95fa4dc9f407dcc4419e87bf"
"sha2": "fb6bdcb35d721efd2efc359911854cdd2834eece"
}
,{
"testCaseDescription": "javascript-variable-delete-insert-test",
"expectedResult": {
"changes": {
"variable.js": [
"Replaced the 'theVar2' identifier with the 'theVar' identifier"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
8
]
},
{
"start": [
1,
1
],
"end": [
1,
7
]
}
]
},
"summary": "Replaced the 'theVar2' identifier with the 'theVar' identifier"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"variable.js"
],
"sha1": "0930920535116a7d95fa4dc9f407dcc4419e87bf",
"sha1": "fb6bdcb35d721efd2efc359911854cdd2834eece",
"gitDir": "test/corpus/repos/javascript",
"sha2": "5f888716fe2b1d0b09397606a4b35e6b53e25913"
"sha2": "b49f639a28f9a64cb9c8994eb626c0353b3b8d34"
}
,{
"testCaseDescription": "javascript-variable-replacement-test",
"expectedResult": {
"changes": {
"variable.js": [
"Replaced the 'theVar' identifier with the 'theVar2' identifier"
{
"span": {
"replace": [
{
"start": [
1,
1
],
"end": [
1,
7
]
},
{
"start": [
1,
1
],
"end": [
1,
8
]
}
]
},
"summary": "Replaced the 'theVar' identifier with the 'theVar2' identifier"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"variable.js"
],
"sha1": "5f888716fe2b1d0b09397606a4b35e6b53e25913",
"sha1": "b49f639a28f9a64cb9c8994eb626c0353b3b8d34",
"gitDir": "test/corpus/repos/javascript",
"sha2": "de30641d2a7cb742bcccf8b9c0eacfdcc135c2f8"
"sha2": "26355d52a696edb7b9cc3fd119c6f5fd6afdd24c"
}
,{
"testCaseDescription": "javascript-variable-delete-replacement-test",
"expectedResult": {
"changes": {
"variable.js": [
"Deleted the 'theVar2' identifier",
"Deleted the 'theVar' identifier",
"Added the 'theVar2' identifier"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'theVar2' identifier"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
7
]
}
},
"summary": "Deleted the 'theVar' identifier"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
8
]
}
},
"summary": "Added the 'theVar2' identifier"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"variable.js"
],
"sha1": "de30641d2a7cb742bcccf8b9c0eacfdcc135c2f8",
"sha1": "26355d52a696edb7b9cc3fd119c6f5fd6afdd24c",
"gitDir": "test/corpus/repos/javascript",
"sha2": "35b8622366444128642e104f0f084873dd3ef727"
"sha2": "c7eb7e72c8e57e95670f442f9a1129a19a4864bd"
}
,{
"testCaseDescription": "javascript-variable-delete-test",
"expectedResult": {
"changes": {
"variable.js": [
"Deleted the 'theVar' identifier"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
7
]
}
},
"summary": "Deleted the 'theVar' identifier"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"variable.js"
],
"sha1": "35b8622366444128642e104f0f084873dd3ef727",
"sha1": "c7eb7e72c8e57e95670f442f9a1129a19a4864bd",
"gitDir": "test/corpus/repos/javascript",
"sha2": "a9c86a2bafcb9ed5028d8b950030a9a31cab9c23"
"sha2": "3d7a287fb605880675b46eba44ecfaab86e8ba35"
}
,{
"testCaseDescription": "javascript-variable-delete-rest-test",
"expectedResult": {
"changes": {
"variable.js": [
"Deleted the 'theVar2' identifier"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
8
]
}
},
"summary": "Deleted the 'theVar2' identifier"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"variable.js"
],
"sha1": "a9c86a2bafcb9ed5028d8b950030a9a31cab9c23",
"sha1": "3d7a287fb605880675b46eba44ecfaab86e8ba35",
"gitDir": "test/corpus/repos/javascript",
"sha2": "b3b641ed7deb3f41fd97836c9026ce33eeba4a48"
"sha2": "7ad1f0f1e9c4fda88ae65caff85d855f6b429c0f"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"void-operator.js": [
"Added the 'void b()' operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
9
]
}
},
"summary": "Added the 'void b()' operator"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"void-operator.js"
],
"sha1": "f2894107b28e50c3ab3c6a0528d509364f55fccc",
"sha1": "7ba29898c7f45897e7de7f1191e0c6b7f9fac35e",
"gitDir": "test/corpus/repos/javascript",
"sha2": "265e3fad5fb536c10088f508929ae90fc180d9a9"
"sha2": "04efcf66ddcaa70558821725988f42c1af11f3cc"
}
,{
"testCaseDescription": "javascript-void-operator-replacement-insert-test",
"expectedResult": {
"changes": {
"void-operator.js": [
"Added the 'void c()' operator",
"Added the 'void b()' operator"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
9
]
}
},
"summary": "Added the 'void c()' operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Added the 'void b()' operator"
}
]
},
"errors": {}
@ -29,16 +71,42 @@
"filePaths": [
"void-operator.js"
],
"sha1": "265e3fad5fb536c10088f508929ae90fc180d9a9",
"sha1": "04efcf66ddcaa70558821725988f42c1af11f3cc",
"gitDir": "test/corpus/repos/javascript",
"sha2": "2b2a51d4fb02b5bebf0ea34ecaefb361ad80463a"
"sha2": "2cfcfeb87a2b4a0db7905bc74d3a7e1be38cbf5a"
}
,{
"testCaseDescription": "javascript-void-operator-delete-insert-test",
"expectedResult": {
"changes": {
"void-operator.js": [
"Replaced the 'c' identifier with the 'b' identifier in the b() function call"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
7
]
},
{
"start": [
1,
6
],
"end": [
1,
7
]
}
]
},
"summary": "Replaced the 'c' identifier with the 'b' identifier in the b() function call"
}
]
},
"errors": {}
@ -46,16 +114,42 @@
"filePaths": [
"void-operator.js"
],
"sha1": "2b2a51d4fb02b5bebf0ea34ecaefb361ad80463a",
"sha1": "2cfcfeb87a2b4a0db7905bc74d3a7e1be38cbf5a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7c0d513d3809d081ec09a436b015053985ecb206"
"sha2": "cd22e88db42b827ae56fb6ca9edeb221c67f038d"
}
,{
"testCaseDescription": "javascript-void-operator-replacement-test",
"expectedResult": {
"changes": {
"void-operator.js": [
"Replaced the 'b' identifier with the 'c' identifier in the c() function call"
{
"span": {
"replace": [
{
"start": [
1,
6
],
"end": [
1,
7
]
},
{
"start": [
1,
6
],
"end": [
1,
7
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'c' identifier in the c() function call"
}
]
},
"errors": {}
@ -63,18 +157,60 @@
"filePaths": [
"void-operator.js"
],
"sha1": "7c0d513d3809d081ec09a436b015053985ecb206",
"sha1": "cd22e88db42b827ae56fb6ca9edeb221c67f038d",
"gitDir": "test/corpus/repos/javascript",
"sha2": "7e237076aa3f997b8471fbeaed6ed554c44345d8"
"sha2": "0b81ec59795d14187d78eb1f48b8b5e8acb0c748"
}
,{
"testCaseDescription": "javascript-void-operator-delete-replacement-test",
"expectedResult": {
"changes": {
"void-operator.js": [
"Deleted the 'void c()' operator",
"Deleted the 'void b()' operator",
"Added the 'void c()' operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
9
]
}
},
"summary": "Deleted the 'void c()' operator"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Deleted the 'void b()' operator"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
9
]
}
},
"summary": "Added the 'void c()' operator"
}
]
},
"errors": {}
@ -82,16 +218,30 @@
"filePaths": [
"void-operator.js"
],
"sha1": "7e237076aa3f997b8471fbeaed6ed554c44345d8",
"sha1": "0b81ec59795d14187d78eb1f48b8b5e8acb0c748",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4321017fac27cd83890a791bb104f5fb8b637bfd"
"sha2": "9860d6a2ad25819e82ac0848010b5d6f7e1b5b76"
}
,{
"testCaseDescription": "javascript-void-operator-delete-test",
"expectedResult": {
"changes": {
"void-operator.js": [
"Deleted the 'void b()' operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
9
]
}
},
"summary": "Deleted the 'void b()' operator"
}
]
},
"errors": {}
@ -99,16 +249,30 @@
"filePaths": [
"void-operator.js"
],
"sha1": "4321017fac27cd83890a791bb104f5fb8b637bfd",
"sha1": "9860d6a2ad25819e82ac0848010b5d6f7e1b5b76",
"gitDir": "test/corpus/repos/javascript",
"sha2": "21081c2fb2503a7a371d8d0943a77523a96b992f"
"sha2": "df7dcb8b1dbc8cd8d7044c0ea75c825e95f55279"
}
,{
"testCaseDescription": "javascript-void-operator-delete-rest-test",
"expectedResult": {
"changes": {
"void-operator.js": [
"Deleted the 'void c()' operator"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
9
]
}
},
"summary": "Deleted the 'void c()' operator"
}
]
},
"errors": {}
@ -116,7 +280,7 @@
"filePaths": [
"void-operator.js"
],
"sha1": "21081c2fb2503a7a371d8d0943a77523a96b992f",
"sha1": "df7dcb8b1dbc8cd8d7044c0ea75c825e95f55279",
"gitDir": "test/corpus/repos/javascript",
"sha2": "70a57d3ee8bb0f31663af70c592c7e294522a194"
"sha2": "85ef535e2b1570133c3be4bddaffc8513555ad2c"
}]

View File

@ -3,7 +3,21 @@
"expectedResult": {
"changes": {
"while-statement.js": [
"Added the 'a' while statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
19
]
}
},
"summary": "Added the 'a' while statement"
}
]
},
"errors": {}
@ -11,17 +25,45 @@
"filePaths": [
"while-statement.js"
],
"sha1": "194fb9e98c554553e25a4f30b4bb5d1fe67a8d21",
"sha1": "1476b59a288eafecf5ddd48696a3e207754a9668",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f03a86242f6d7e0c2158c1bd91117ff5f134244a"
"sha2": "f23284bfe8af3aeae4cd0de9ff318f5c0bb1117a"
}
,{
"testCaseDescription": "javascript-while-statement-replacement-insert-test",
"expectedResult": {
"changes": {
"while-statement.js": [
"Added the 'b' while statement",
"Added the 'a' while statement"
{
"span": {
"insert": {
"start": [
1,
1
],
"end": [
1,
19
]
}
},
"summary": "Added the 'b' while statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Added the 'a' while statement"
}
]
},
"errors": {}
@ -29,17 +71,69 @@
"filePaths": [
"while-statement.js"
],
"sha1": "f03a86242f6d7e0c2158c1bd91117ff5f134244a",
"sha1": "f23284bfe8af3aeae4cd0de9ff318f5c0bb1117a",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4b5f53810edb5d664d12ab15115b0e2cd12883c3"
"sha2": "0187cf96aade757c54df567264bce2b15c5d2bde"
}
,{
"testCaseDescription": "javascript-while-statement-delete-insert-test",
"expectedResult": {
"changes": {
"while-statement.js": [
"Replaced the 'b' identifier with the 'a' identifier",
"Replaced the 'a' identifier with the 'b' identifier in the b() function call"
{
"span": {
"replace": [
{
"start": [
1,
8
],
"end": [
1,
9
]
},
{
"start": [
1,
8
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'a' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
13
],
"end": [
1,
14
]
},
{
"start": [
1,
13
],
"end": [
1,
14
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'b' identifier in the b() function call"
}
]
},
"errors": {}
@ -47,17 +141,69 @@
"filePaths": [
"while-statement.js"
],
"sha1": "4b5f53810edb5d664d12ab15115b0e2cd12883c3",
"sha1": "0187cf96aade757c54df567264bce2b15c5d2bde",
"gitDir": "test/corpus/repos/javascript",
"sha2": "f820f59d00d6d5666ff278bb88b0872d69ebfe62"
"sha2": "ea3cd5cf3a270d94a6fb64540f5d15c3a862d7db"
}
,{
"testCaseDescription": "javascript-while-statement-replacement-test",
"expectedResult": {
"changes": {
"while-statement.js": [
"Replaced the 'a' identifier with the 'b' identifier",
"Replaced the 'b' identifier with the 'a' identifier in the a() function call"
{
"span": {
"replace": [
{
"start": [
1,
8
],
"end": [
1,
9
]
},
{
"start": [
1,
8
],
"end": [
1,
9
]
}
]
},
"summary": "Replaced the 'a' identifier with the 'b' identifier"
},
{
"span": {
"replace": [
{
"start": [
1,
13
],
"end": [
1,
14
]
},
{
"start": [
1,
13
],
"end": [
1,
14
]
}
]
},
"summary": "Replaced the 'b' identifier with the 'a' identifier in the a() function call"
}
]
},
"errors": {}
@ -65,18 +211,60 @@
"filePaths": [
"while-statement.js"
],
"sha1": "f820f59d00d6d5666ff278bb88b0872d69ebfe62",
"sha1": "ea3cd5cf3a270d94a6fb64540f5d15c3a862d7db",
"gitDir": "test/corpus/repos/javascript",
"sha2": "4434ecd0b9e69ea4196f2deba5982a527b3e4160"
"sha2": "201605c6796eb154347d09577ba30c428ff8a2fe"
}
,{
"testCaseDescription": "javascript-while-statement-delete-replacement-test",
"expectedResult": {
"changes": {
"while-statement.js": [
"Deleted the 'b' while statement",
"Deleted the 'a' while statement",
"Added the 'b' while statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
19
]
}
},
"summary": "Deleted the 'b' while statement"
},
{
"span": {
"delete": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Deleted the 'a' while statement"
},
{
"span": {
"insert": {
"start": [
2,
1
],
"end": [
2,
19
]
}
},
"summary": "Added the 'b' while statement"
}
]
},
"errors": {}
@ -84,16 +272,30 @@
"filePaths": [
"while-statement.js"
],
"sha1": "4434ecd0b9e69ea4196f2deba5982a527b3e4160",
"sha1": "201605c6796eb154347d09577ba30c428ff8a2fe",
"gitDir": "test/corpus/repos/javascript",
"sha2": "402eab49ccde91b2c9efa1356c6a66c2fb49c153"
"sha2": "b6a9d4096d663c0a0095d75e9ceb4dacf5bbee39"
}
,{
"testCaseDescription": "javascript-while-statement-delete-test",
"expectedResult": {
"changes": {
"while-statement.js": [
"Deleted the 'a' while statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
19
]
}
},
"summary": "Deleted the 'a' while statement"
}
]
},
"errors": {}
@ -101,16 +303,30 @@
"filePaths": [
"while-statement.js"
],
"sha1": "402eab49ccde91b2c9efa1356c6a66c2fb49c153",
"sha1": "b6a9d4096d663c0a0095d75e9ceb4dacf5bbee39",
"gitDir": "test/corpus/repos/javascript",
"sha2": "faa78f18bece2461d747ffa915cf3f4d62b42582"
"sha2": "a82434bad4b9b59f0d6df675bc4fadfa97b992b4"
}
,{
"testCaseDescription": "javascript-while-statement-delete-rest-test",
"expectedResult": {
"changes": {
"while-statement.js": [
"Deleted the 'b' while statement"
{
"span": {
"delete": {
"start": [
1,
1
],
"end": [
1,
19
]
}
},
"summary": "Deleted the 'b' while statement"
}
]
},
"errors": {}
@ -118,7 +334,7 @@
"filePaths": [
"while-statement.js"
],
"sha1": "faa78f18bece2461d747ffa915cf3f4d62b42582",
"sha1": "a82434bad4b9b59f0d6df675bc4fadfa97b992b4",
"gitDir": "test/corpus/repos/javascript",
"sha2": "cf72590c7112ba5cf176106991fc2d91400204fd"
"sha2": "ff624cef881f79c1f5e43043657a490eb7d137e2"
}]

@ -1 +1 @@
Subproject commit 7e9421a0f261a2de196d05d153a86dc4c8340351
Subproject commit dce5b472e5bcc43861e65b412644c7931f12d313