mirror of
https://github.com/github/semantic.git
synced 2025-01-08 08:30:27 +03:00
Merge pull request #755 from github/api-changes
API Changes to --summary output
This commit is contained in:
commit
5ee3d197da
@ -1,6 +1,6 @@
|
||||
{-# LANGUAGE DataKinds, TypeFamilies, ScopedTypeVariables #-}
|
||||
|
||||
module DiffSummary (DiffSummary(..), diffSummaries, DiffInfo(..), annotatedSummaries) where
|
||||
module DiffSummary (diffSummaries, DiffSummary(..), DiffInfo(..), diffToDiffSummaries, isBranchInfo) where
|
||||
|
||||
import Prologue hiding (intercalate)
|
||||
import Diff
|
||||
@ -34,11 +34,18 @@ data DiffSummary a = DiffSummary {
|
||||
parentAnnotation :: Maybe (Category, Text)
|
||||
} deriving (Eq, Functor, Show, Generic)
|
||||
|
||||
annotatedSummaries :: DiffSummary DiffInfo -> [Text]
|
||||
annotatedSummaries DiffSummary{..} = show . (P.<> maybeParentContext parentAnnotation) <$> summaries patch
|
||||
-- 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 -> Diff leaf (Record fields) -> [Either Text Text]
|
||||
diffSummaries blobs diff = summaryToTexts =<< diffToDiffSummaries (source <$> blobs) diff
|
||||
|
||||
diffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range) => Both (Source Char) -> Diff leaf (Record fields) -> [DiffSummary DiffInfo]
|
||||
diffSummaries sources = para $ \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 . (P.<> maybeParentContext parentAnnotation)) <$> (Join <$> 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) -> Diff leaf (Record fields) -> [DiffSummary DiffInfo]
|
||||
diffToDiffSummaries sources = para $ \diff ->
|
||||
let diff' = free (Prologue.fst <$> diff)
|
||||
annotateWithCategory :: [(Diff leaf (Record fields), [DiffSummary DiffInfo])] -> [DiffSummary DiffInfo]
|
||||
annotateWithCategory children = maybeToList (prependSummary (Both.snd sources) <$> (afterTerm diff')) <*> (children >>= snd) in
|
||||
@ -49,23 +56,35 @@ diffSummaries 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
|
||||
|
||||
summaries :: Patch DiffInfo -> [P.Doc]
|
||||
summaries (Insert info) = uncurry (prefixOrErrorDoc "Added") <$> toLeafInfos info
|
||||
summaries (Delete info) = uncurry (prefixOrErrorDoc "Deleted") <$> toLeafInfos info
|
||||
summaries (Replace i1 i2) = zipWith (\a b -> uncurry (prefixOrErrorDoc "Replaced") a <+> "with the" <+> snd b) (toLeafInfos i1) (toLeafInfos i2)
|
||||
-- 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 the" <+> b) (toLeafInfos i1) (toLeafInfos i2)
|
||||
p@(Insert info) -> (prefixWithPatch p) <$> toLeafInfos info
|
||||
p@(Delete info) -> (prefixWithPatch p) <$> toLeafInfos info
|
||||
|
||||
prefixOrErrorDoc :: Text -> DiffInfo -> Doc -> Doc
|
||||
prefixOrErrorDoc prefix info doc = message <+> string (toSL prefix) <+> "the" <+> doc
|
||||
where message = case info of
|
||||
ErrorInfo{} -> "Diff Summary Error:"
|
||||
_ -> mempty
|
||||
-- Prefixes a given doc with the type of patch it represents.
|
||||
prefixWithPatch :: Patch DiffInfo -> Doc -> Doc
|
||||
prefixWithPatch patch = prefixWithThe (patchToPrefix patch)
|
||||
where
|
||||
prefixWithThe prefix doc = prefix <+> "the" <+> doc
|
||||
patchToPrefix = \case
|
||||
(Replace _ _) -> "Replaced"
|
||||
(Insert _) -> "Added"
|
||||
(Delete _) -> "Deleted"
|
||||
|
||||
toLeafInfos :: DiffInfo -> [(DiffInfo, Doc)]
|
||||
toLeafInfos info@LeafInfo{..} = pure (info, squotes (toDoc termName) <+> (toDoc categoryName))
|
||||
toLeafInfos :: DiffInfo -> [Doc]
|
||||
toLeafInfos LeafInfo{..} = pure (squotes (toDoc termName) <+> (toDoc categoryName))
|
||||
toLeafInfos BranchInfo{..} = toLeafInfos =<< branches
|
||||
toLeafInfos err@ErrorInfo{} = pure (err, pretty err)
|
||||
toLeafInfos err@ErrorInfo{} = pure (pretty err)
|
||||
|
||||
-- Returns a text representing a specific term given a source and a term.
|
||||
toTermName :: (HasCategory leaf, HasField fields Category, HasField fields Range) => Source Char -> Term leaf (Record fields) -> Text
|
||||
toTermName source term = case unwrap term of
|
||||
S.AnonymousFunction _ _ -> "anonymous"
|
||||
@ -169,6 +188,17 @@ prependSummary source term summary = if (isNothing $ parentAnnotation summary) &
|
||||
S.Method{} -> True
|
||||
_ -> False
|
||||
|
||||
isBranchInfo :: DiffInfo -> Bool
|
||||
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
|
||||
|
@ -36,7 +36,7 @@ import TreeSitter
|
||||
import Text.Parser.TreeSitter.Language
|
||||
import qualified Data.Text as T
|
||||
import Category
|
||||
import Data.Aeson (pairs)
|
||||
import Data.Aeson (toJSON, toEncoding)
|
||||
import Data.Aeson.Encoding (encodingToLazyByteString)
|
||||
|
||||
-- | Given a parser and renderer, diff two sources and return the rendered
|
||||
@ -165,8 +165,8 @@ printDiff parser arguments sources = do
|
||||
let renderedText = case rendered of
|
||||
SplitOutput text -> text
|
||||
PatchOutput text -> text
|
||||
JSONOutput series -> toS . encodingToLazyByteString $ pairs series
|
||||
SummaryOutput summaries -> toS . encodingToLazyByteString $ pairs summaries
|
||||
JSONOutput series -> toS . encodingToLazyByteString . toEncoding $ toJSON series
|
||||
SummaryOutput summaries -> toS . encodingToLazyByteString . toEncoding $ toJSON summaries
|
||||
|
||||
case output arguments of
|
||||
Nothing -> TextIO.putStr renderedText
|
||||
|
@ -7,6 +7,7 @@ import Data.String
|
||||
import Prologue
|
||||
import Test.QuickCheck
|
||||
|
||||
|
||||
-- | A half-open interval of integers, defined by start & end indices.
|
||||
data Range = Range { start :: !Int, end :: !Int }
|
||||
deriving (Eq, Show)
|
||||
|
@ -1,12 +1,13 @@
|
||||
module Renderer (Renderer, DiffArguments(..), Output(..), concatOutputs, Format(..)) where
|
||||
module Renderer (Renderer, DiffArguments(..), Output(..), concatOutputs, toSummaryKey, Format(..)) where
|
||||
|
||||
import Prologue
|
||||
import Data.Functor.Both
|
||||
import Diff
|
||||
import Source (SourceBlob)
|
||||
import Data.Aeson.Types (Series, pairs)
|
||||
import Data.Text as T (intercalate)
|
||||
import Data.Aeson (Value, toEncoding)
|
||||
import Data.Aeson.Encoding (encodingToLazyByteString)
|
||||
import Data.Map as Map hiding (null)
|
||||
|
||||
-- | A function that will render a diff, given the two source blobs.
|
||||
type Renderer annotation = Both SourceBlob -> Diff Text annotation -> Output
|
||||
@ -14,24 +15,57 @@ type Renderer annotation = Both SourceBlob -> Diff Text annotation -> Output
|
||||
data DiffArguments = DiffArguments { format :: Format, output :: Maybe FilePath, outputPath :: FilePath }
|
||||
deriving (Show)
|
||||
|
||||
data Output = SplitOutput Text | PatchOutput Text | JSONOutput Series | SummaryOutput Series
|
||||
-- | The available types of diff rendering.
|
||||
data Format = Split | Patch | JSON | Summary
|
||||
deriving (Show)
|
||||
|
||||
data Output = SplitOutput Text | PatchOutput Text | JSONOutput (Map Text Value) | SummaryOutput (Map Text (Map Text [Text]))
|
||||
deriving (Show)
|
||||
|
||||
-- Returns a key representing the filename. If the filenames are different,
|
||||
-- return 'before -> after'.
|
||||
toSummaryKey :: Both FilePath -> Text
|
||||
toSummaryKey = runBothWith $ \before after ->
|
||||
toS $ case (before, after) of
|
||||
("", after) -> after
|
||||
(before, "") -> before
|
||||
(before, after) | before == after -> after
|
||||
(before, after) | not (null before) && not (null after) -> before <> " -> " <> after
|
||||
(_, _) -> mempty
|
||||
|
||||
-- Concatenates a list of 'Output' depending on the output type.
|
||||
-- For JSON, each file output is merged since they're uniquely keyed by filename.
|
||||
-- For Summaries, each file output is merged into one 'Object' consisting of lists of
|
||||
-- changes and errors.
|
||||
-- Split and Patch output is appended together with newlines.
|
||||
concatOutputs :: [Output] -> Text
|
||||
concatOutputs l@(JSONOutput _ : _) = toS . encodingToLazyByteString . pairs . mconcat $ toSeries <$> l
|
||||
concatOutputs l@(SummaryOutput _ : _) = toS . encodingToLazyByteString . pairs . mconcat $ toSeries <$> l
|
||||
concatOutputs l = T.intercalate "\n" (toText <$> l)
|
||||
concatOutputs list | isJSON list = toS . encodingToLazyByteString . toEncoding $ concatJSON list
|
||||
where
|
||||
concatJSON :: [Output] -> Map Text Value
|
||||
concatJSON (JSONOutput hash : rest) = Map.union hash (concatJSON rest)
|
||||
concatJSON _ = mempty
|
||||
concatOutputs list | isSummary list = toS . encodingToLazyByteString . toEncoding $ concatSummaries list
|
||||
where
|
||||
concatSummaries :: [Output] -> Map Text (Map Text [Text])
|
||||
concatSummaries (SummaryOutput hash : rest) = Map.unionWith (Map.unionWith (<>)) hash (concatSummaries rest)
|
||||
concatSummaries _ = mempty
|
||||
concatOutputs list | isText list = T.intercalate "\n" (toText <$> list)
|
||||
concatOutputs _ = mempty
|
||||
|
||||
toSeries :: Output -> Series
|
||||
toSeries (JSONOutput series) = series
|
||||
toSeries (SummaryOutput series) = series
|
||||
toSeries _ = mempty
|
||||
isJSON :: [Output] -> Bool
|
||||
isJSON (JSONOutput _ : _) = True
|
||||
isJSON _ = False
|
||||
|
||||
isSummary :: [Output] -> Bool
|
||||
isSummary (SummaryOutput _ : _) = True
|
||||
isSummary _ = False
|
||||
|
||||
isText :: [Output] -> Bool
|
||||
isText (SplitOutput _ : _) = True
|
||||
isText (PatchOutput _ : _) = True
|
||||
isText _ = False
|
||||
|
||||
toText :: Output -> Text
|
||||
toText (SplitOutput text) = text
|
||||
toText (PatchOutput text) = text
|
||||
toText _ = mempty
|
||||
|
||||
|
||||
-- | The available types of diff rendering.
|
||||
data Format = Split | Patch | JSON | Summary
|
||||
deriving (Show)
|
||||
|
@ -12,19 +12,24 @@ import Data.Bifunctor.Join
|
||||
import Data.Record
|
||||
import qualified Data.Text as T
|
||||
import Data.These
|
||||
import Data.Vector hiding (toList)
|
||||
import Data.Vector as Vector hiding (toList)
|
||||
import Info
|
||||
import Renderer
|
||||
import Source hiding (fromList)
|
||||
import SplitDiff
|
||||
import Syntax as S
|
||||
import Term
|
||||
import qualified Data.Map as Map
|
||||
|
||||
-- | Render a diff to a string representing its JSON.
|
||||
json :: (HasField fields Category, HasField fields Range) => Renderer (Record fields)
|
||||
json blobs diff = JSONOutput $ "rows" .= annotateRows (alignDiff (source <$> blobs) diff) <> "oids" .= (oid <$> blobs) <> "paths" .= (path <$> blobs)
|
||||
json blobs diff = JSONOutput $ Map.fromList [
|
||||
("rows", toJSON (annotateRows (alignDiff (source <$> blobs) diff))),
|
||||
("oids", toJSON (oid <$> blobs)),
|
||||
("paths", toJSON (path <$> blobs)) ]
|
||||
where annotateRows = fmap (fmap NumberedLine) . numberedRows
|
||||
|
||||
-- | A numbered 'a'.
|
||||
newtype NumberedLine a = NumberedLine (Int, a)
|
||||
|
||||
instance (HasField fields Category, HasField fields Range) => ToJSON (NumberedLine (SplitDiff leaf (Record fields))) where
|
||||
@ -34,14 +39,13 @@ instance ToJSON Category where
|
||||
toJSON (Other s) = String s
|
||||
toJSON s = String . T.pack $ show s
|
||||
instance ToJSON Range where
|
||||
toJSON (Range start end) = A.Array . fromList $ toJSON <$> [ start, end ]
|
||||
toJSON (Range start end) = A.Array . Vector.fromList $ toJSON <$> [ start, end ]
|
||||
toEncoding (Range start end) = foldable [ start, end ]
|
||||
instance ToJSON a => ToJSON (Join These a) where
|
||||
toJSON (Join vs) = A.Array . fromList $ toJSON <$> these pure pure (\ a b -> [ a, b ]) vs
|
||||
toJSON (Join vs) = A.Array . Vector.fromList $ toJSON <$> these pure pure (\ a b -> [ a, b ]) vs
|
||||
toEncoding = foldable
|
||||
instance ToJSON a => ToJSON (Join (,) a) where
|
||||
toJSON (Join (a, b)) = A.Array . fromList $ toJSON <$> [ a, b ]
|
||||
toEncoding = foldable
|
||||
toJSON (Join (a, b)) = A.Array . Vector.fromList $ toJSON <$> [ a, b ]
|
||||
instance (HasField fields Category, HasField fields Range) => ToJSON (SplitDiff leaf (Record fields)) where
|
||||
toJSON splitDiff = case runFree splitDiff of
|
||||
(Free (info :< syntax)) -> object (termFields info syntax)
|
||||
|
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
module Renderer.Summary where
|
||||
|
||||
import Category
|
||||
@ -6,11 +7,17 @@ import Renderer
|
||||
import Data.Record
|
||||
import Range
|
||||
import DiffSummary
|
||||
import Data.Map as Map hiding (null)
|
||||
import Source
|
||||
import Data.Aeson
|
||||
import Data.Functor.Both (runBothWith)
|
||||
|
||||
summary :: (HasField fields Category, HasField fields Range) => Renderer (Record fields)
|
||||
summary blobs diff = SummaryOutput $ (runBothWith toSummaryKey (path <$> blobs)) .= (summaries >>= annotatedSummaries)
|
||||
where summaries = diffSummaries (source <$> blobs) diff
|
||||
toSummaryKey before after = toS $ if before == after then after else before <> " -> " <> after
|
||||
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
|
||||
summaryKey = toSummaryKey (path <$> blobs)
|
||||
summaries = diffSummaries blobs diff
|
||||
|
@ -35,29 +35,24 @@ testSummary = DiffSummary { patch = Insert (LeafInfo "string" "a"), parentAnnota
|
||||
replacementSummary :: DiffSummary DiffInfo
|
||||
replacementSummary = DiffSummary { patch = Replace (LeafInfo "string" "a") (LeafInfo "symbol" "b"), parentAnnotation = Just (Info.FunctionCall, "foo") }
|
||||
|
||||
sources :: Both (Source Char)
|
||||
sources = both (fromText "[]") (fromText "[a]")
|
||||
blobs :: Both SourceBlob
|
||||
blobs = both (SourceBlob (fromText "[]") nullOid "a.js" (Just defaultPlainBlob)) (SourceBlob (fromText "[a]") nullOid "b.js" (Just defaultPlainBlob))
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "diffSummaries" $ do
|
||||
it "outputs a diff summary" $ do
|
||||
diffSummaries sources testDiff `shouldBe` [ DiffSummary { patch = Insert (LeafInfo "string" "a"), parentAnnotation = Nothing } ]
|
||||
diffSummaries blobs testDiff `shouldBe` [ Right $ "Added the 'a' string" ]
|
||||
|
||||
prop "equal terms produce identity diffs" $
|
||||
\ a -> let term = defaultFeatureVectorDecorator (category . headF) (toTerm (a :: ArbitraryTerm Text (Record '[Category, Range]))) in
|
||||
diffSummaries sources (diffTerms wrap (==) diffCost term term) `shouldBe` []
|
||||
diffSummaries blobs (diffTerms wrap (==) diffCost term term) `shouldBe` []
|
||||
|
||||
describe "annotatedSummaries" $ do
|
||||
it "should print adds" $
|
||||
annotatedSummaries testSummary `shouldBe` ["Added the 'a' string"]
|
||||
it "prints a replacement" $ do
|
||||
annotatedSummaries replacementSummary `shouldBe` ["Replaced the 'a' string with the 'b' symbol in the foo function call"]
|
||||
describe "DiffInfo" $ do
|
||||
prop "patches in summaries match the patches in diffs" $
|
||||
\a -> let
|
||||
diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category, Cost, Range])))
|
||||
summaries = diffSummaries sources diff
|
||||
summaries = diffToDiffSummaries (source <$> blobs) diff
|
||||
patches = toList diff
|
||||
in
|
||||
case (partition isBranchNode (patch <$> summaries), partition isIndexedOrFixed patches) of
|
||||
@ -66,7 +61,7 @@ spec = parallel $ do
|
||||
prop "generates one LeafInfo for each child in an arbitrary branch patch" $
|
||||
\a -> let
|
||||
diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category, Range])))
|
||||
diffInfoPatches = patch <$> diffSummaries sources diff
|
||||
diffInfoPatches = patch <$> diffToDiffSummaries (source <$> blobs) diff
|
||||
syntaxPatches = toList diff
|
||||
extractLeaves :: DiffInfo -> [DiffInfo]
|
||||
extractLeaves (BranchInfo children _ _) = join $ extractLeaves <$> children
|
||||
@ -95,10 +90,5 @@ isIndexedOrFixed' syntax = case syntax of
|
||||
(Fixed _) -> True
|
||||
_ -> False
|
||||
|
||||
isBranchInfo :: DiffInfo -> Bool
|
||||
isBranchInfo info = case info of
|
||||
(BranchInfo _ _ _) -> True
|
||||
_ -> False
|
||||
|
||||
isBranchNode :: Patch DiffInfo -> Bool
|
||||
isBranchNode = any isBranchInfo
|
||||
|
@ -1 +1 @@
|
||||
{"rows":[[{"number":1,"terms":[{"range":[0,2],"category":"Program","children":[{"range":[0,2],"category":"ExpressionStatements","children":[{"range":[0,2],"category":"Object","children":[]}]}]}],"range":[0,2],"hasChanges":false},{"number":1,"terms":[{"range":[0,2],"category":"Program","children":[{"range":[0,2],"category":"ExpressionStatements","children":[{"range":[0,2],"category":"Object","children":[]}]}]}],"range":[0,2],"hasChanges":false}],[{"number":2,"terms":[{"range":[2,12],"category":"Program","children":[{"range":[2,12],"category":"ExpressionStatements","children":[{"range":[2,12],"category":"Object","children":[{"range":[4,10],"category":"Pair","children":[{"range":[4,7],"category":"StringLiteral","children":[{"range":[4,5],"category":"StringLiteral"},{"range":[5,6],"category":"StringLiteral"},{"range":[6,7],"category":"StringLiteral"}]},{"patch":"replace","range":[9,10],"category":"number"}]}]}]}]}],"range":[2,12],"hasChanges":true},{"number":2,"terms":[{"range":[2,12],"category":"Program","children":[{"range":[2,12],"category":"ExpressionStatements","children":[{"range":[2,12],"category":"Object","children":[{"range":[4,10],"category":"Pair","children":[{"range":[4,7],"category":"StringLiteral","children":[{"range":[4,5],"category":"StringLiteral"},{"range":[5,6],"category":"StringLiteral"},{"range":[6,7],"category":"StringLiteral"}]},{"patch":"replace","range":[9,10],"category":"number"}]}]}]}]}],"range":[2,12],"hasChanges":true}],[{"number":3,"terms":[{"range":[12,21],"category":"Program","children":[{"range":[12,21],"category":"ExpressionStatements","children":[{"range":[12,21],"category":"Object","children":[{"range":[14,20],"category":"Pair","children":[{"range":[14,17],"category":"StringLiteral","children":[{"range":[14,15],"category":"StringLiteral"},{"range":[15,16],"category":"StringLiteral"},{"range":[16,17],"category":"StringLiteral"}]},{"range":[19,20],"category":"number"}]}]}]}]}],"range":[12,21],"hasChanges":false},{"number":3,"terms":[{"range":[12,21],"category":"Program","children":[{"range":[12,21],"category":"ExpressionStatements","children":[{"range":[12,21],"category":"Object","children":[{"range":[14,20],"category":"Pair","children":[{"range":[14,17],"category":"StringLiteral","children":[{"range":[14,15],"category":"StringLiteral"},{"range":[15,16],"category":"StringLiteral"},{"range":[16,17],"category":"StringLiteral"}]},{"range":[19,20],"category":"number"}]}]}]}]}],"range":[12,21],"hasChanges":false}],[{"number":4,"terms":[{"range":[21,23],"category":"Program","children":[{"range":[21,23],"category":"ExpressionStatements","children":[{"range":[21,22],"category":"Object","children":[]}]}]}],"range":[21,23],"hasChanges":false},{"number":4,"terms":[{"range":[21,23],"category":"Program","children":[{"range":[21,23],"category":"ExpressionStatements","children":[{"range":[21,22],"category":"Object","children":[]}]}]}],"range":[21,23],"hasChanges":false}],[{"number":5,"terms":[{"range":[23,23],"category":"Program","children":[]}],"range":[23,23],"hasChanges":false},{"number":5,"terms":[{"range":[23,23],"category":"Program","children":[]}],"range":[23,23],"hasChanges":false}]],"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/dictionary.A.js","test/diffs/dictionary.B.js"]}
|
||||
{"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/dictionary.A.js","test/diffs/dictionary.B.js"],"rows":[[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"Object","children":[],"range":[0,2]}],"range":[0,2]}],"range":[0,2]}],"hasChanges":false,"range":[0,2],"number":1},{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"Object","children":[],"range":[0,2]}],"range":[0,2]}],"range":[0,2]}],"hasChanges":false,"range":[0,2],"number":1}],[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"Object","children":[{"category":"Pair","children":[{"category":"StringLiteral","children":[{"category":"StringLiteral","range":[4,5]},{"category":"StringLiteral","range":[5,6]},{"category":"StringLiteral","range":[6,7]}],"range":[4,7]},{"category":"number","patch":"replace","range":[9,10]}],"range":[4,10]}],"range":[2,12]}],"range":[2,12]}],"range":[2,12]}],"hasChanges":true,"range":[2,12],"number":2},{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"Object","children":[{"category":"Pair","children":[{"category":"StringLiteral","children":[{"category":"StringLiteral","range":[4,5]},{"category":"StringLiteral","range":[5,6]},{"category":"StringLiteral","range":[6,7]}],"range":[4,7]},{"category":"number","patch":"replace","range":[9,10]}],"range":[4,10]}],"range":[2,12]}],"range":[2,12]}],"range":[2,12]}],"hasChanges":true,"range":[2,12],"number":2}],[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"Object","children":[{"category":"Pair","children":[{"category":"StringLiteral","children":[{"category":"StringLiteral","range":[14,15]},{"category":"StringLiteral","range":[15,16]},{"category":"StringLiteral","range":[16,17]}],"range":[14,17]},{"category":"number","range":[19,20]}],"range":[14,20]}],"range":[12,21]}],"range":[12,21]}],"range":[12,21]}],"hasChanges":false,"range":[12,21],"number":3},{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"Object","children":[{"category":"Pair","children":[{"category":"StringLiteral","children":[{"category":"StringLiteral","range":[14,15]},{"category":"StringLiteral","range":[15,16]},{"category":"StringLiteral","range":[16,17]}],"range":[14,17]},{"category":"number","range":[19,20]}],"range":[14,20]}],"range":[12,21]}],"range":[12,21]}],"range":[12,21]}],"hasChanges":false,"range":[12,21],"number":3}],[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"Object","children":[],"range":[21,22]}],"range":[21,23]}],"range":[21,23]}],"hasChanges":false,"range":[21,23],"number":4},{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"Object","children":[],"range":[21,22]}],"range":[21,23]}],"range":[21,23]}],"hasChanges":false,"range":[21,23],"number":4}],[{"terms":[{"category":"Program","children":[],"range":[23,23]}],"hasChanges":false,"range":[23,23],"number":5},{"terms":[{"category":"Program","children":[],"range":[23,23]}],"hasChanges":false,"range":[23,23],"number":5}]]}
|
@ -1 +1 @@
|
||||
{"rows":[[{"number":1,"terms":[{"range":[0,29],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}],"range":[0,29],"hasChanges":false},{"number":1,"terms":[{"range":[0,29],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}],"range":[0,29],"hasChanges":false}],[{"number":2,"terms":[{"range":[29,29],"category":"Program","children":[]}],"range":[29,29],"hasChanges":false},{"number":2,"terms":[{"range":[29,30],"category":"Program","children":[]}],"range":[29,30],"hasChanges":false}],[{"number":3,"terms":[{"range":[30,56],"category":"Program","children":[{"patch":"insert","range":[30,55],"category":"ExpressionStatements","children":[{"range":[30,54],"category":"MethodCall","children":[{"range":[30,37],"category":"Identifier"},{"range":[38,41],"category":"Identifier"},{"range":[42,53],"category":"StringLiteral","children":[{"range":[42,43],"category":"StringLiteral"},{"range":[43,52],"category":"StringLiteral"},{"range":[52,53],"category":"StringLiteral"}]}]}]}]}],"range":[30,56],"hasChanges":true}],[{"number":4,"terms":[{"range":[56,56],"category":"Program","children":[]}],"range":[56,56],"hasChanges":false}]],"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/newline-at-eof.A.js","test/diffs/newline-at-eof.B.js"]}
|
||||
{"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/newline-at-eof.A.js","test/diffs/newline-at-eof.B.js"],"rows":[[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","children":[{"category":"StringLiteral","range":[12,13]},{"category":"StringLiteral","range":[13,18]},{"category":"StringLiteral","range":[18,19]},{"category":"StringLiteral","range":[20,25]},{"category":"StringLiteral","range":[25,26]}],"range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,29]}],"hasChanges":false,"range":[0,29],"number":1},{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","children":[{"category":"StringLiteral","range":[12,13]},{"category":"StringLiteral","range":[13,18]},{"category":"StringLiteral","range":[18,19]},{"category":"StringLiteral","range":[20,25]},{"category":"StringLiteral","range":[25,26]}],"range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,29]}],"hasChanges":false,"range":[0,29],"number":1}],[{"terms":[{"category":"Program","children":[],"range":[29,29]}],"hasChanges":false,"range":[29,29],"number":2},{"terms":[{"category":"Program","children":[],"range":[29,30]}],"hasChanges":false,"range":[29,30],"number":2}],[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[30,37]},{"category":"Identifier","range":[38,41]},{"category":"StringLiteral","children":[{"category":"StringLiteral","range":[42,43]},{"category":"StringLiteral","range":[43,52]},{"category":"StringLiteral","range":[52,53]}],"range":[42,53]}],"range":[30,54]}],"patch":"insert","range":[30,55]}],"range":[30,56]}],"hasChanges":true,"range":[30,56],"number":3}],[{"terms":[{"category":"Program","children":[],"range":[56,56]}],"hasChanges":false,"range":[56,56],"number":4}]]}
|
@ -1 +1 @@
|
||||
{"rows":[[{"number":1,"terms":[{"range":[0,28],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}],"range":[0,28],"hasChanges":false},{"number":1,"terms":[{"range":[0,29],"category":"Program","children":[{"range":[0,28],"category":"ExpressionStatements","children":[{"range":[0,27],"category":"MethodCall","children":[{"range":[0,7],"category":"Identifier"},{"range":[8,11],"category":"Identifier"},{"range":[12,26],"category":"StringLiteral","children":[{"range":[12,13],"category":"StringLiteral"},{"range":[13,18],"category":"StringLiteral"},{"range":[18,19],"category":"StringLiteral"},{"range":[20,25],"category":"StringLiteral"},{"range":[25,26],"category":"StringLiteral"}]}]}]}]}],"range":[0,29],"hasChanges":false}],[{"number":2,"terms":[{"range":[29,30],"category":"Program","children":[]}],"range":[29,30],"hasChanges":false}],[{"number":3,"terms":[{"range":[30,55],"category":"Program","children":[{"patch":"insert","range":[30,55],"category":"ExpressionStatements","children":[{"range":[30,54],"category":"MethodCall","children":[{"range":[30,37],"category":"Identifier"},{"range":[38,41],"category":"Identifier"},{"range":[42,53],"category":"StringLiteral","children":[{"range":[42,43],"category":"StringLiteral"},{"range":[43,52],"category":"StringLiteral"},{"range":[52,53],"category":"StringLiteral"}]}]}]}]}],"range":[30,55],"hasChanges":true}]],"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/no-newline-at-eof.A.js","test/diffs/no-newline-at-eof.B.js"]}
|
||||
{"oids":["0000000000000000000000000000000000000000","0000000000000000000000000000000000000000"],"paths":["test/diffs/no-newline-at-eof.A.js","test/diffs/no-newline-at-eof.B.js"],"rows":[[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","children":[{"category":"StringLiteral","range":[12,13]},{"category":"StringLiteral","range":[13,18]},{"category":"StringLiteral","range":[18,19]},{"category":"StringLiteral","range":[20,25]},{"category":"StringLiteral","range":[25,26]}],"range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,28]}],"hasChanges":false,"range":[0,28],"number":1},{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[0,7]},{"category":"Identifier","range":[8,11]},{"category":"StringLiteral","children":[{"category":"StringLiteral","range":[12,13]},{"category":"StringLiteral","range":[13,18]},{"category":"StringLiteral","range":[18,19]},{"category":"StringLiteral","range":[20,25]},{"category":"StringLiteral","range":[25,26]}],"range":[12,26]}],"range":[0,27]}],"range":[0,28]}],"range":[0,29]}],"hasChanges":false,"range":[0,29],"number":1}],[{"terms":[{"category":"Program","children":[],"range":[29,30]}],"hasChanges":false,"range":[29,30],"number":2}],[{"terms":[{"category":"Program","children":[{"category":"ExpressionStatements","children":[{"category":"MethodCall","children":[{"category":"Identifier","range":[30,37]},{"category":"Identifier","range":[38,41]},{"category":"StringLiteral","children":[{"category":"StringLiteral","range":[42,43]},{"category":"StringLiteral","range":[43,52]},{"category":"StringLiteral","range":[52,53]}],"range":[42,53]}],"range":[30,54]}],"patch":"insert","range":[30,55]}],"range":[30,55]}],"hasChanges":true,"range":[30,55],"number":3}]]}
|
Loading…
Reference in New Issue
Block a user