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

Merge branch 'master' into crashers-gonna-crash

This commit is contained in:
Josh Vera 2016-03-02 12:24:40 -05:00
commit 2c0014f26e
13 changed files with 160 additions and 45 deletions

View File

@ -32,6 +32,7 @@ library
, Patch
, Range
, Renderer
, Renderer.JSON
, Renderer.Patch
, Renderer.Split
, Row
@ -41,7 +42,8 @@ library
, Syntax
, Term
, TreeSitter
build-depends: base >= 4.8 && < 5
build-depends: aeson
, base >= 4.8 && < 5
, blaze-html
, blaze-markup
, bytestring

View File

@ -4,6 +4,7 @@ import Category
import Control.Comonad.Cofree
import Control.Monad.Free
import Data.Either
import Data.Foldable (foldl')
import Data.Functor.Both
import Data.Functor.Identity
import qualified Data.OrderedMap as Map
@ -20,6 +21,18 @@ import SplitDiff
import Syntax
import Term
-- | Assign line numbers to the lines on each side of a list of rows.
numberedRows :: [Row a] -> [Both (Int, Line a)]
numberedRows = foldl' numberRows []
where numberRows rows row = ((,) <$> ((+) <$> count rows <*> (valueOf <$> unRow row)) <*> unRow row) : rows
count = maybe (pure 0) (fmap Prelude.fst) . maybeFirst
valueOf EmptyLine = 0
valueOf _ = 1
-- | Determine whether a line contains any patches.
hasChanges :: Line (SplitDiff leaf Info) -> Bool
hasChanges = or . fmap (or . (True <$))
-- | Split a diff, which may span multiple lines, into rows of split diffs.
splitDiffByLines :: Diff leaf Info -> Both Int -> Both (Source Char) -> ([Row (SplitDiff leaf Info)], Both Range)
splitDiffByLines diff previous sources = case diff of

View File

@ -10,7 +10,7 @@ import Syntax
import Term
-- | An annotated syntax in a diff tree.
data Annotated a annotation f = Annotated !annotation !(Syntax a f)
data Annotated a annotation f = Annotated { annotation :: !annotation, syntax :: !(Syntax a f) }
deriving (Functor, Eq, Show, Foldable)
-- | An annotation for a source file, including the source range and semantic

View File

@ -1,18 +1,20 @@
module DiffOutput where
import qualified Data.ByteString.Lazy as B
import qualified Data.Text.Lazy.IO as TextIO
import Data.Functor.Both
import Diffing
import Parser
import qualified Renderer.JSON as J
import qualified Renderer.Patch as P
import Renderer.Split
import Source
import System.Directory
import System.FilePath
import qualified System.IO as IO
import qualified Data.Text.Lazy.IO as TextIO
import qualified Renderer.Patch as P
import Renderer.Split
-- | The available types of diff rendering.
data Format = Split | Patch
data Format = Split | Patch | JSON
data DiffArguments = DiffArguments { format :: Format, output :: Maybe FilePath, outputPath :: FilePath }
@ -29,3 +31,4 @@ printDiff parser arguments sources = case format arguments of
else path
IO.withFile outputPath IO.WriteMode (`TextIO.hPutStr` rendered)
Patch -> putStr =<< diffFiles parser P.patch sources
JSON -> B.putStr =<< diffFiles parser J.json sources

81
src/Renderer/JSON.hs Normal file
View File

@ -0,0 +1,81 @@
{-# LANGUAGE FlexibleInstances, OverloadedStrings, TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Renderer.JSON (
json
) where
import Alignment
import Category
import Control.Comonad.Cofree
import Control.Monad.Free
import Data.Aeson hiding (json)
import Data.ByteString.Builder
import Data.ByteString.Lazy
import Data.Functor.Both
import Data.Monoid
import Data.OrderedMap hiding (fromList)
import qualified Data.Text as T
import Data.Vector hiding (toList)
import Diff
import Line
import Range
import Renderer
import Source hiding (fromList, toList)
import SplitDiff
import Syntax
import Term
-- | Render a diff to a string representing its JSON.
json :: Renderer a ByteString
json diff sources = toLazyByteString . fromEncoding . pairs $
"rows" .= annotateRows (Prelude.fst (splitDiffByLines diff (pure 0) (source <$> sources)))
<> "oids" .= (oid <$> sources)
<> "paths" .= (path <$> sources)
where annotateRows = fmap (fmap NumberedLine) . Prelude.reverse . numberedRows
newtype NumberedLine a = NumberedLine (Int, Line a)
instance ToJSON (NumberedLine (SplitDiff leaf Info)) where
toJSON (NumberedLine (n, a)) = object (lineFields n a)
toEncoding (NumberedLine (n, a)) = pairs $ mconcat (lineFields n a)
instance ToJSON Category where
toJSON (Other s) = String $ T.pack s
toJSON s = String . T.pack $ show s
instance ToJSON Range where
toJSON (Range start end) = Array . fromList $ toJSON <$> [ start, end ]
toEncoding (Range start end) = foldable [ start, end ]
instance ToJSON a => ToJSON (Both a) where
toJSON (Both (a, b)) = Array . fromList $ toJSON <$> [ a, b ]
toEncoding both = foldable both
instance ToJSON (SplitDiff leaf Info) where
toJSON (Free (Annotated info syntax)) = object (termFields info syntax)
toJSON (Pure patch) = object (patchFields patch)
toEncoding (Free (Annotated info syntax)) = pairs $ mconcat (termFields info syntax)
toEncoding (Pure patch) = pairs $ mconcat (patchFields patch)
instance ToJSON value => ToJSON (OrderedMap T.Text value) where
toJSON map = object $ uncurry (.=) <$> toList map
toEncoding map = pairs . mconcat $ uncurry (.=) <$> toList map
instance ToJSON (Term leaf Info) where
toJSON (info :< syntax) = object (termFields info syntax)
toEncoding (info :< syntax) = pairs $ mconcat (termFields info syntax)
lineFields :: KeyValue kv => Int -> Line (SplitDiff leaf Info) -> [kv]
lineFields _ EmptyLine = []
lineFields n line = [ "number" .= n, "terms" .= unLine line, "range" .= unionRanges (getRange <$> line), "hasChanges" .= hasChanges line ]
where getRange (Free (Annotated (Info range _) _)) = range
getRange (Pure patch) = case getSplitTerm patch of Info range _ :< _ -> range
termFields :: (ToJSON recur, KeyValue kv) => Info -> Syntax leaf recur -> [kv]
termFields (Info range categories) syntax = "range" .= range : "categories" .= categories : case syntax of
Leaf _ -> []
Indexed c -> childrenFields c
Fixed c -> childrenFields c
Keyed c -> childrenFields c
where childrenFields c = [ "children" .= c ]
patchFields :: KeyValue kv => SplitPatch (Cofree (Syntax leaf) Info) -> [kv]
patchFields patch = case patch of
SplitInsert term -> fields "insert" term
SplitDelete term -> fields "delete" term
SplitReplace term -> fields "replace" term
where fields kind (info :< syntax) = "patch" .= T.pack kind : termFields info syntax

View File

@ -3,29 +3,28 @@ module Renderer.Split where
import Alignment
import Category
import Control.Comonad.Cofree
import Control.Monad.Free
import Data.Foldable
import Data.Functor.Both
import Data.Monoid
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Diff
import Line
import Prelude hiding (div, head, span, fst, snd)
import qualified Prelude
import Row
import Range
import Renderer
import Term
import Source hiding ((++))
import SplitDiff
import Syntax
import Control.Comonad.Cofree
import Range
import Control.Monad.Free
import Term
import Text.Blaze.Html
import Text.Blaze.Html5 hiding (map)
import qualified Text.Blaze.Internal as Blaze
import qualified Text.Blaze.Html5.Attributes as A
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Text.Blaze.Html.Renderer.Text
import Data.Functor.Both
import Data.Foldable
import Data.Monoid
import Source hiding ((++))
import Text.Blaze.Html5 hiding (map)
import qualified Text.Blaze.Html5.Attributes as A
import qualified Text.Blaze.Internal as Blaze
type ClassName = T.Text
@ -65,7 +64,7 @@ split diff blobs = renderHtml
where
sources = Source.source <$> blobs
rows = Prelude.fst (splitDiffByLines diff (pure 0) sources)
numbered = foldl' numberRows [] rows
numbered = numberedRows rows
maxNumber = case numbered of
[] -> 0
(row : _) -> runBothWith max $ Prelude.fst <$> row
@ -82,17 +81,7 @@ split diff blobs = renderHtml
numberedLinesToMarkup numberedLines = tr $ (runBothWith (<>) (renderLine <$> numberedLines <*> sources)) <> string "\n"
renderLine :: (Int, Line (SplitDiff leaf Info)) -> Source Char -> Markup
renderLine (number, line) source = toMarkup $ Renderable (or $ hasChanges <$> line, number, Renderable . (,) source <$> line)
hasChanges diff = or $ const True <$> diff
-- | Add a row to list of tuples of ints and lines, where the ints denote
-- | how many non-empty lines exist on that side up to that point.
numberRows :: [Both (Int, Line a)] -> Row a -> [Both (Int, Line a)]
numberRows rows row = ((,) <$> ((+) <$> count rows <*> (valueOf <$> unRow row)) <*> unRow row) : rows
where count = maybe (pure 0) (fmap Prelude.fst) . maybeFirst
valueOf EmptyLine = 0
valueOf _ = 1
renderLine (number, line) source = toMarkup $ Renderable (hasChanges line, number, Renderable . (,) source <$> line)
-- | Something that can be rendered as markup.
newtype Renderable a = Renderable a

View File

@ -6,7 +6,7 @@ import Term (Term)
-- | A patch to only one side of a diff.
data SplitPatch a = SplitInsert a | SplitDelete a | SplitReplace a
deriving (Show, Eq)
deriving (Show, Eq, Functor)
-- | Get the term from a split patch.
getSplitTerm :: SplitPatch a -> a

View File

@ -2,12 +2,13 @@ module CorpusSpec where
import Diffing
import Renderer
import qualified Renderer.JSON as J
import qualified Renderer.Patch as P
import qualified Renderer.Split as Split
import Control.DeepSeq
import Data.Functor.Both
import qualified Data.ByteString.Char8 as B1
import qualified Data.ByteString.Lazy.Char8 as B
import Data.List as List
import Data.Map as Map
import Data.Maybe
@ -39,27 +40,29 @@ spec = parallel $ do
let tests = correctTests =<< paths
mapM_ (\ (formatName, renderer, paths, output) -> it (normalizeName (fst paths) ++ " (" ++ formatName ++ ")") $ testDiff renderer paths output matcher) tests
correctTests :: (Both FilePath, Maybe FilePath, Maybe FilePath) -> [(String, Renderer a String, Both FilePath, Maybe FilePath)]
correctTests paths@(_, Nothing, Nothing) = testsForPaths paths
correctTests :: (Both FilePath, Maybe FilePath, Maybe FilePath, Maybe FilePath) -> [(String, Renderer a String, Both FilePath, Maybe FilePath)]
correctTests paths@(_, Nothing, Nothing, Nothing) = testsForPaths paths
correctTests paths = List.filter (\(_, _, _, output) -> isJust output) $ testsForPaths paths
testsForPaths :: (Both FilePath, Maybe FilePath, Maybe FilePath) -> [(String, Renderer a String, Both FilePath, Maybe FilePath)]
testsForPaths (paths, patch, split) = [ ("patch", P.patch, paths, patch), ("split", testSplit, paths, split) ]
testsForPaths :: (Both FilePath, Maybe FilePath, Maybe FilePath, Maybe FilePath) -> [(String, Renderer a String, Both FilePath, Maybe FilePath)]
testsForPaths (paths, json, patch, split) = [ ("json", testJSON, paths, json), ("patch", P.patch, paths, patch), ("split", testSplit, paths, split) ]
testSplit :: Renderer a String
testSplit diff sources = TL.unpack $ Split.split diff sources
testJSON :: Renderer a String
testJSON diff sources = B.unpack $ J.json diff sources
-- | Return all the examples from the given directory. Examples are expected to
-- | have the form "foo.A.js", "foo.B.js", "foo.patch.js". Diffs are not
-- | required as the test may be verifying that the inputs don't crash.
examples :: FilePath -> IO [(Both FilePath, Maybe FilePath, Maybe FilePath)]
examples :: FilePath -> IO [(Both FilePath, Maybe FilePath, Maybe FilePath, Maybe FilePath)]
examples directory = do
as <- toDict <$> globFor "*.A.*"
bs <- toDict <$> globFor "*.B.*"
jsons <- toDict <$> globFor "*.json.*"
patches <- toDict <$> globFor "*.patch.*"
splits <- toDict <$> globFor "*.split.*"
let keys = Set.unions $ keysSet <$> [as, bs]
return $ (\name -> (Both (as ! name, bs ! name), Map.lookup name patches, Map.lookup name splits)) <$> sort (Set.toList keys)
return $ (\name -> (Both (as ! name, bs ! name), Map.lookup name jsons, Map.lookup name patches, Map.lookup name splits)) <$> sort (Set.toList keys)
where
globFor :: String -> IO [FilePath]
globFor p = globDir1 (compile p) directory

View File

@ -0,0 +1 @@
{"rows":[[{"number":1,"terms":[{"range":[0,2],"categories":["program"],"children":[{"range":[0,2],"categories":["expression_statement"],"children":[{"range":[0,2],"categories":["DictionaryLiteral"],"children":{}}]}]}],"range":[0,2],"hasChanges":false},{"number":1,"terms":[{"range":[0,2],"categories":["program"],"children":[{"range":[0,2],"categories":["expression_statement"],"children":[{"range":[0,2],"categories":["DictionaryLiteral"],"children":{}}]}]}],"range":[0,2],"hasChanges":false}],[{"number":2,"terms":[{"range":[2,12],"categories":["program"],"children":[{"range":[2,12],"categories":["expression_statement"],"children":[{"range":[2,12],"categories":["DictionaryLiteral"],"children":{"\"b\"":{"range":[4,10],"categories":["Pair"],"children":[{"range":[4,7],"categories":["StringLiteral"],"children":[{"range":[4,5],"categories":["StringLiteral"]},{"range":[5,6],"categories":["StringLiteral"]},{"range":[6,7],"categories":["StringLiteral"]}]},{"patch":"replace","range":[9,10],"categories":["number"]}]}}}]}]}],"range":[2,12],"hasChanges":true},{"number":2,"terms":[{"range":[2,12],"categories":["program"],"children":[{"range":[2,12],"categories":["expression_statement"],"children":[{"range":[2,12],"categories":["DictionaryLiteral"],"children":{"\"b\"":{"range":[4,10],"categories":["Pair"],"children":[{"range":[4,7],"categories":["StringLiteral"],"children":[{"range":[4,5],"categories":["StringLiteral"]},{"range":[5,6],"categories":["StringLiteral"]},{"range":[6,7],"categories":["StringLiteral"]}]},{"patch":"replace","range":[9,10],"categories":["number"]}]}}}]}]}],"range":[2,12],"hasChanges":true}],[{"number":3,"terms":[{"range":[12,21],"categories":["program"],"children":[{"range":[12,21],"categories":["expression_statement"],"children":[{"range":[12,21],"categories":["DictionaryLiteral"],"children":{"\"a\"":{"range":[14,20],"categories":["Pair"],"children":[{"range":[14,17],"categories":["StringLiteral"],"children":[{"range":[14,15],"categories":["StringLiteral"]},{"range":[15,16],"categories":["StringLiteral"]},{"range":[16,17],"categories":["StringLiteral"]}]},{"range":[19,20],"categories":["number"]}]}}}]}]}],"range":[12,21],"hasChanges":false},{"number":3,"terms":[{"range":[12,21],"categories":["program"],"children":[{"range":[12,21],"categories":["expression_statement"],"children":[{"range":[12,21],"categories":["DictionaryLiteral"],"children":{"\"a\"":{"range":[14,20],"categories":["Pair"],"children":[{"range":[14,17],"categories":["StringLiteral"],"children":[{"range":[14,15],"categories":["StringLiteral"]},{"range":[15,16],"categories":["StringLiteral"]},{"range":[16,17],"categories":["StringLiteral"]}]},{"range":[19,20],"categories":["number"]}]}}}]}]}],"range":[12,21],"hasChanges":false}],[{"number":4,"terms":[{"range":[21,23],"categories":["program"],"children":[{"range":[21,23],"categories":["expression_statement"],"children":[{"range":[21,22],"categories":["DictionaryLiteral"],"children":{}}]}]}],"range":[21,23],"hasChanges":false},{"number":4,"terms":[{"range":[21,23],"categories":["program"],"children":[{"range":[21,23],"categories":["expression_statement"],"children":[{"range":[21,22],"categories":["DictionaryLiteral"],"children":{}}]}]}],"range":[21,23],"hasChanges":false}],[{"number":5,"terms":[{"range":[23,23],"categories":["program"],"children":[{"range":[23,23],"categories":["expression_statement"],"children":[]}]}],"range":[23,23],"hasChanges":false},{"number":5,"terms":[{"range":[23,23],"categories":["program"],"children":[{"range":[23,23],"categories":["expression_statement"],"children":[]}]}],"range":[23,23],"hasChanges":false}]],"oids":["",""],"paths":["test/diffs/dictionary.A.js","test/diffs/dictionary.B.js"]}

View File

@ -0,0 +1,25 @@
<!DOCTYPE HTML>
<html><head><link rel="stylesheet" href="style.css"></head><body><table class="diff"><colgroup><col width="40"><col><col width="40"><col></colgroup><tr><td class="blob-num">1</td><td class="blob-code"><ul class="category-program"><li><ul class="category-expression_statement"><li><dl class="category-dictionary">{
</dl></li></ul></li></ul></td>
<td class="blob-num">1</td><td class="blob-code"><ul class="category-program"><li><ul class="category-expression_statement"><li><dl class="category-dictionary">{
</dl></li></ul></li></ul></td>
</tr><tr><td class="blob-num blob-num-replacement">2</td><td class="blob-code blob-code-replacement"><ul class="category-program"><li><ul class="category-expression_statement"><li><dl class="category-dictionary"> <dd><ul class="category-pair"><li><ul class="category-string"><li><span class="category-string">&quot;</span></li><li><span class="category-string">b</span></li><li><span class="category-string">&quot;</span></li></ul></li>: <li><div class="patch replace" data="1"><span class="category-number">4</span></div></li></ul></dd>,
</dl></li></ul></li></ul></td>
<td class="blob-num blob-num-replacement">2</td><td class="blob-code blob-code-replacement"><ul class="category-program"><li><ul class="category-expression_statement"><li><dl class="category-dictionary"> <dd><ul class="category-pair"><li><ul class="category-string"><li><span class="category-string">&quot;</span></li><li><span class="category-string">b</span></li><li><span class="category-string">&quot;</span></li></ul></li>: <li><div class="patch replace" data="1"><span class="category-number">5</span></div></li></ul></dd>,
</dl></li></ul></li></ul></td>
</tr><tr><td class="blob-num">3</td><td class="blob-code"><ul class="category-program"><li><ul class="category-expression_statement"><li><dl class="category-dictionary"> <dd><ul class="category-pair"><li><ul class="category-string"><li><span class="category-string">&quot;</span></li><li><span class="category-string">a</span></li><li><span class="category-string">&quot;</span></li></ul></li>: <li><span class="category-number">5</span></li></ul></dd>
</dl></li></ul></li></ul></td>
<td class="blob-num">3</td><td class="blob-code"><ul class="category-program"><li><ul class="category-expression_statement"><li><dl class="category-dictionary"> <dd><ul class="category-pair"><li><ul class="category-string"><li><span class="category-string">&quot;</span></li><li><span class="category-string">a</span></li><li><span class="category-string">&quot;</span></li></ul></li>: <li><span class="category-number">5</span></li></ul></dd>
</dl></li></ul></li></ul></td>
</tr><tr><td class="blob-num">4</td><td class="blob-code"><ul class="category-program"><li><ul class="category-expression_statement"><li><dl class="category-dictionary">}</dl></li>
</ul></li></ul></td>
<td class="blob-num">4</td><td class="blob-code"><ul class="category-program"><li><ul class="category-expression_statement"><li><dl class="category-dictionary">}</dl></li>
</ul></li></ul></td>
</tr><tr><td class="blob-num">5</td><td class="blob-code"><ul class="category-program"><li><ul class="category-expression_statement"></ul></li></ul></td>
<td class="blob-num">5</td><td class="blob-code"><ul class="category-program"><li><ul class="category-expression_statement"></ul></li></ul></td>
</tr></table></body></html>

View File

@ -1,4 +0,0 @@
{
"b": {-4-}{+5+},
"a": 5
}

View File

@ -0,0 +1 @@
{"rows":[[{"number":1,"terms":[{"range":[0,29],"categories":["program"],"children":[{"range":[0,28],"categories":["expression_statement"],"children":[{"range":[0,27],"categories":["FunctionCall"],"children":[{"range":[0,11],"categories":["member_access"],"children":[{"range":[0,7],"categories":["identifier"]},{"range":[8,11],"categories":["identifier"]}]},{"range":[12,26],"categories":["arguments"],"children":[{"range":[12,26],"categories":["StringLiteral"],"children":[{"range":[12,13],"categories":["StringLiteral"]},{"range":[13,18],"categories":["StringLiteral"]},{"range":[18,19],"categories":["StringLiteral"]},{"range":[20,25],"categories":["StringLiteral"]},{"range":[25,26],"categories":["StringLiteral"]}]}]}]}]}]}],"range":[0,29],"hasChanges":false},{"number":1,"terms":[{"range":[0,29],"categories":["program"],"children":[{"range":[0,28],"categories":["expression_statement"],"children":[{"range":[0,27],"categories":["FunctionCall"],"children":[{"range":[0,11],"categories":["member_access"],"children":[{"range":[0,7],"categories":["identifier"]},{"range":[8,11],"categories":["identifier"]}]},{"range":[12,26],"categories":["arguments"],"children":[{"range":[12,26],"categories":["StringLiteral"],"children":[{"range":[12,13],"categories":["StringLiteral"]},{"range":[13,18],"categories":["StringLiteral"]},{"range":[18,19],"categories":["StringLiteral"]},{"range":[20,25],"categories":["StringLiteral"]},{"range":[25,26],"categories":["StringLiteral"]}]}]}]}]}]}],"range":[0,29],"hasChanges":false}],[{},{"number":2,"terms":[{"range":[29,30],"categories":["program"],"children":[]}],"range":[29,30],"hasChanges":false}],[{},{"number":3,"terms":[{"range":[30,56],"categories":["program"],"children":[{"patch":"insert","range":[30,55],"categories":["expression_statement"],"children":[{"range":[30,54],"categories":["FunctionCall"],"children":[{"range":[30,41],"categories":["member_access"],"children":[{"range":[30,37],"categories":["identifier"]},{"range":[38,41],"categories":["identifier"]}]},{"range":[42,53],"categories":["arguments"],"children":[{"range":[42,53],"categories":["StringLiteral"],"children":[{"range":[42,43],"categories":["StringLiteral"]},{"range":[43,52],"categories":["StringLiteral"]},{"range":[52,53],"categories":["StringLiteral"]}]}]}]}]}]}],"range":[30,56],"hasChanges":true}],[{"number":2,"terms":[{"range":[29,29],"categories":["program"],"children":[]}],"range":[29,29],"hasChanges":false},{"number":4,"terms":[{"range":[56,56],"categories":["program"],"children":[]}],"range":[56,56],"hasChanges":false}]],"oids":["",""],"paths":["test/diffs/newline-at-eof.A.js","test/diffs/newline-at-eof.B.js"]}

View File

@ -0,0 +1 @@
{"rows":[[{"number":1,"terms":[{"range":[0,28],"categories":["program"],"children":[{"range":[0,28],"categories":["expression_statement"],"children":[{"range":[0,27],"categories":["FunctionCall"],"children":[{"range":[0,11],"categories":["member_access"],"children":[{"range":[0,7],"categories":["identifier"]},{"range":[8,11],"categories":["identifier"]}]},{"range":[12,26],"categories":["arguments"],"children":[{"range":[12,26],"categories":["StringLiteral"],"children":[{"range":[12,13],"categories":["StringLiteral"]},{"range":[13,18],"categories":["StringLiteral"]},{"range":[18,19],"categories":["StringLiteral"]},{"range":[20,25],"categories":["StringLiteral"]},{"range":[25,26],"categories":["StringLiteral"]}]}]}]}]}]}],"range":[0,28],"hasChanges":false},{"number":1,"terms":[{"range":[0,29],"categories":["program"],"children":[{"range":[0,28],"categories":["expression_statement"],"children":[{"range":[0,27],"categories":["FunctionCall"],"children":[{"range":[0,11],"categories":["member_access"],"children":[{"range":[0,7],"categories":["identifier"]},{"range":[8,11],"categories":["identifier"]}]},{"range":[12,26],"categories":["arguments"],"children":[{"range":[12,26],"categories":["StringLiteral"],"children":[{"range":[12,13],"categories":["StringLiteral"]},{"range":[13,18],"categories":["StringLiteral"]},{"range":[18,19],"categories":["StringLiteral"]},{"range":[20,25],"categories":["StringLiteral"]},{"range":[25,26],"categories":["StringLiteral"]}]}]}]}]}]}],"range":[0,29],"hasChanges":false}],[{},{"number":2,"terms":[{"range":[29,30],"categories":["program"],"children":[]}],"range":[29,30],"hasChanges":false}],[{},{"number":3,"terms":[{"range":[30,55],"categories":["program"],"children":[{"patch":"insert","range":[30,55],"categories":["expression_statement"],"children":[{"range":[30,54],"categories":["FunctionCall"],"children":[{"range":[30,41],"categories":["member_access"],"children":[{"range":[30,37],"categories":["identifier"]},{"range":[38,41],"categories":["identifier"]}]},{"range":[42,53],"categories":["arguments"],"children":[{"range":[42,53],"categories":["StringLiteral"],"children":[{"range":[42,43],"categories":["StringLiteral"]},{"range":[43,52],"categories":["StringLiteral"]},{"range":[52,53],"categories":["StringLiteral"]}]}]}]}]}]}],"range":[30,55],"hasChanges":true}]],"oids":["",""],"paths":["test/diffs/no-newline-at-eof.A.js","test/diffs/no-newline-at-eof.B.js"]}