2017-05-09 17:19:45 +03:00
{- # OPTIONS_GHC - fno - warn - orphans # -}
2017-05-11 22:53:22 +03:00
{- # LANGUAGE DataKinds, TypeOperators # -}
2017-02-14 22:29:24 +03:00
module TOCSpec where
2017-02-15 21:15:57 +03:00
import Category as C
2017-07-28 21:37:02 +03:00
import Data.Aeson
2017-09-14 04:37:23 +03:00
import Data.Bifunctor
2017-06-24 17:09:50 +03:00
import Data.Blob
2017-07-28 21:37:02 +03:00
import Data.ByteString ( ByteString )
2017-02-14 22:29:24 +03:00
import Data.Functor.Both
2017-02-15 21:15:57 +03:00
import Data.Functor.Listable
2017-07-28 21:37:02 +03:00
import Data.Maybe ( fromMaybe )
import Data.Monoid ( Last ( .. ) )
2017-07-28 18:23:55 +03:00
import Data.Output
2017-02-14 22:29:24 +03:00
import Data.Record
2017-07-28 21:37:02 +03:00
import Data.Semigroup ( ( <> ) )
2017-06-24 16:59:41 +03:00
import Data.Source
2017-07-28 21:37:02 +03:00
import Data.Text ( Text )
2017-05-11 23:37:08 +03:00
import Data.These
2017-02-14 22:29:24 +03:00
import Diff
import Info
2017-02-14 22:54:32 +03:00
import Interpreter
2017-05-10 01:49:38 +03:00
import Language
2017-02-14 23:48:34 +03:00
import Patch
2017-07-28 21:37:02 +03:00
import Prelude hiding ( readFile )
2017-04-20 02:33:27 +03:00
import Renderer
2017-02-14 22:54:32 +03:00
import Renderer.TOC
2017-05-11 17:00:11 +03:00
import RWS
import Semantic
2017-05-30 17:29:37 +03:00
import Semantic.Task
2017-05-11 17:00:11 +03:00
import SpecHelpers
2017-02-17 02:22:46 +03:00
import Syntax as S
2017-02-15 21:15:57 +03:00
import Term
2017-02-14 22:29:24 +03:00
import Test.Hspec ( Spec , describe , it , parallel )
import Test.Hspec.Expectations.Pretty
2017-02-15 21:15:57 +03:00
import Test.Hspec.LeanCheck
2017-02-16 03:13:34 +03:00
import Test.LeanCheck
2017-02-14 22:29:24 +03:00
spec :: Spec
spec = parallel $ do
2017-05-11 00:01:42 +03:00
describe " tableOfContentsBy " $ do
prop " drops all nodes with the constant Nothing function " $
2017-09-14 16:41:52 +03:00
\ diff -> tableOfContentsBy ( const Nothing :: a -> Maybe () ) ( diff :: Diff Syntax () () ) ` shouldBe ` []
2017-05-11 16:27:28 +03:00
2017-09-09 16:30:42 +03:00
let diffSize = max 1 . length . diffPatches
2017-05-11 20:11:16 +03:00
let lastValue a = fromMaybe ( extract a ) ( getLast ( foldMap ( Last . Just ) a ) )
2017-05-11 16:27:28 +03:00
prop " includes all nodes with a constant Just function " $
2017-09-14 16:41:52 +03:00
\ diff -> let diff' = ( diff :: Diff Syntax () () ) in entryPayload <$> tableOfContentsBy ( const ( Just () ) ) diff' ` shouldBe ` replicate ( diffSize diff' ) ()
2017-05-11 16:27:28 +03:00
2017-05-11 17:02:18 +03:00
prop " produces an unchanged entry for identity diffs " $
2017-09-25 17:57:28 +03:00
\ term -> tableOfContentsBy ( Just . termAnnotation ) ( diffSyntaxTerms term term ) ` shouldBe ` [ Unchanged ( lastValue ( term :: Term Syntax ( Record '[Category] ) ) ) ]
2017-05-11 17:02:18 +03:00
2017-05-11 23:37:08 +03:00
prop " produces inserted/deleted/replaced entries for relevant nodes within patches " $
2017-09-14 04:55:41 +03:00
\ p -> tableOfContentsBy ( Just . termAnnotation ) ( patch deleting inserting replacing p )
2017-09-14 04:37:23 +03:00
` shouldBe `
2017-09-14 04:55:41 +03:00
patch ( fmap Deleted ) ( fmap Inserted ) ( const ( fmap Replaced ) ) ( bimap ( foldMap pure ) ( foldMap pure ) ( p :: Patch ( Term Syntax Int ) ( Term Syntax Int ) ) )
2017-05-11 20:11:40 +03:00
2017-05-11 20:48:35 +03:00
prop " produces changed entries for relevant nodes containing irrelevant patches " $
2017-09-14 16:41:52 +03:00
\ diff -> let diff' = merge ( 0 , 0 ) ( Indexed [ bimap ( const 1 ) ( const 1 ) ( diff :: Diff Syntax Int Int ) ] ) in
2017-09-11 22:48:58 +03:00
tableOfContentsBy ( \ ( n ` In ` _ ) -> if n == ( 0 :: Int ) then Just n else Nothing ) diff' ` shouldBe `
2017-09-09 16:28:43 +03:00
if null ( diffPatches diff' ) then [ Unchanged 0 ]
else replicate ( length ( diffPatches diff' ) ) ( Changed 0 )
2017-05-11 20:48:35 +03:00
2017-02-23 07:05:20 +03:00
describe " diffTOC " $ do
2017-02-14 22:29:24 +03:00
it " blank if there are no methods " $
2017-07-20 03:01:59 +03:00
diffTOC blankDiff ` shouldBe ` [ ]
2017-02-14 22:29:24 +03:00
2017-02-15 21:15:57 +03:00
it " summarizes changed methods " $ do
sourceBlobs <- blobsForPaths ( both " ruby/methods.A.rb " " ruby/methods.B.rb " )
2017-05-31 19:27:21 +03:00
Just diff <- runTask ( diffBlobPair IdentityDiffRenderer sourceBlobs )
2017-07-20 03:01:59 +03:00
diffTOC diff ` shouldBe `
2017-06-05 19:45:18 +03:00
[ JSONSummary " Method " " self.foo " ( sourceSpanBetween ( 1 , 1 ) ( 2 , 4 ) ) " added "
, JSONSummary " Method " " bar " ( sourceSpanBetween ( 4 , 1 ) ( 6 , 4 ) ) " modified "
, JSONSummary " Method " " baz " ( sourceSpanBetween ( 4 , 1 ) ( 5 , 4 ) ) " removed " ]
2017-02-17 02:47:18 +03:00
2017-02-14 22:53:25 +03:00
it " dedupes changes in same parent method " $ do
2017-02-17 19:46:56 +03:00
sourceBlobs <- blobsForPaths ( both " javascript/duplicate-parent.A.js " " javascript/duplicate-parent.B.js " )
2017-05-31 19:27:21 +03:00
Just diff <- runTask ( diffBlobPair IdentityDiffRenderer sourceBlobs )
2017-07-20 03:01:59 +03:00
diffTOC diff ` shouldBe `
2017-06-05 19:45:18 +03:00
[ JSONSummary " Function " " myFunction " ( sourceSpanBetween ( 1 , 1 ) ( 6 , 2 ) ) " modified " ]
2017-02-14 22:53:25 +03:00
it " dedupes similar methods " $ do
2017-02-17 19:46:56 +03:00
sourceBlobs <- blobsForPaths ( both " javascript/erroneous-duplicate-method.A.js " " javascript/erroneous-duplicate-method.B.js " )
2017-05-31 19:27:21 +03:00
Just diff <- runTask ( diffBlobPair IdentityDiffRenderer sourceBlobs )
2017-07-20 03:01:59 +03:00
diffTOC diff ` shouldBe `
2017-06-05 19:45:18 +03:00
[ JSONSummary " Function " " performHealthCheck " ( sourceSpanBetween ( 8 , 1 ) ( 29 , 2 ) ) " modified " ]
2017-02-15 21:15:57 +03:00
2017-02-17 19:45:51 +03:00
it " summarizes Go methods with receivers with special formatting " $ do
sourceBlobs <- blobsForPaths ( both " go/method-with-receiver.A.go " " go/method-with-receiver.B.go " )
2017-05-31 19:27:21 +03:00
Just diff <- runTask ( diffBlobPair IdentityDiffRenderer sourceBlobs )
2017-07-20 03:01:59 +03:00
diffTOC diff ` shouldBe `
2017-06-05 19:45:18 +03:00
[ JSONSummary " Method " " (*apiClient) CheckAuth " ( sourceSpanBetween ( 3 , 1 ) ( 3 , 101 ) ) " added " ]
2017-02-17 19:45:51 +03:00
2017-02-17 19:09:42 +03:00
it " summarizes Ruby methods that start with two identifiers " $ do
sourceBlobs <- blobsForPaths ( both " ruby/method-starts-with-two-identifiers.A.rb " " ruby/method-starts-with-two-identifiers.B.rb " )
2017-05-31 19:27:21 +03:00
Just diff <- runTask ( diffBlobPair IdentityDiffRenderer sourceBlobs )
2017-07-20 03:01:59 +03:00
diffTOC diff ` shouldBe `
2017-06-05 19:45:18 +03:00
[ JSONSummary " Method " " foo " ( sourceSpanBetween ( 1 , 1 ) ( 4 , 4 ) ) " modified " ]
2017-02-17 19:09:42 +03:00
2017-02-16 19:29:49 +03:00
it " handles unicode characters in file " $ do
sourceBlobs <- blobsForPaths ( both " ruby/unicode.A.rb " " ruby/unicode.B.rb " )
2017-05-31 19:27:21 +03:00
Just diff <- runTask ( diffBlobPair IdentityDiffRenderer sourceBlobs )
2017-07-20 03:01:59 +03:00
diffTOC diff ` shouldBe `
2017-06-05 19:45:18 +03:00
[ JSONSummary " Method " " foo " ( sourceSpanBetween ( 6 , 1 ) ( 7 , 4 ) ) " added " ]
2017-02-16 19:29:49 +03:00
2017-06-14 20:01:12 +03:00
it " properly slices source blob that starts with a newline and has multi-byte chars " $ do
sourceBlobs <- blobsForPaths ( both " javascript/starts-with-newline.js " " javascript/starts-with-newline.js " )
Just diff <- runTask ( diffBlobPair IdentityDiffRenderer sourceBlobs )
2017-07-20 03:01:59 +03:00
diffTOC diff ` shouldBe ` []
2017-06-14 20:01:12 +03:00
2017-02-17 01:20:22 +03:00
prop " inserts of methods and functions are summarized " $
2017-02-16 23:23:40 +03:00
\ name body ->
2017-09-09 16:18:08 +03:00
let diff = programWithInsert name body
2017-02-17 01:20:22 +03:00
in numTocSummaries diff ` shouldBe ` 1
2017-02-16 23:23:40 +03:00
2017-02-17 01:20:22 +03:00
prop " deletes of methods and functions are summarized " $
2017-02-16 23:23:40 +03:00
\ name body ->
2017-09-09 16:18:08 +03:00
let diff = programWithDelete name body
2017-02-17 01:20:22 +03:00
in numTocSummaries diff ` shouldBe ` 1
prop " replacements of methods and functions are summarized " $
\ name body ->
2017-09-09 16:18:08 +03:00
let diff = programWithReplace name body
2017-05-12 00:09:54 +03:00
in numTocSummaries diff ` shouldBe ` 1
2017-02-16 03:13:34 +03:00
2017-02-17 02:22:46 +03:00
prop " changes inside methods and functions are summarizied " . forAll ( isMeaningfulTerm ` filterT ` tiers ) $
\ body ->
2017-09-09 16:18:08 +03:00
let diff = programWithChange body
2017-02-17 02:22:46 +03:00
in numTocSummaries diff ` shouldBe ` 1
2017-02-17 02:41:13 +03:00
prop " other changes don't summarize " . forAll ( ( not . isMethodOrFunction ) ` filterT ` tiers ) $
\ body ->
2017-09-09 16:18:08 +03:00
let diff = programWithChangeOutsideFunction body
2017-02-17 02:41:13 +03:00
in numTocSummaries diff ` shouldBe ` 0
2017-02-15 21:15:57 +03:00
prop " equal terms produce identity diffs " $
2017-09-09 16:18:08 +03:00
\ a -> let term = defaultFeatureVectorDecorator ( Info . category . termAnnotation ) ( a :: Term' ) in
2017-09-25 17:57:28 +03:00
diffTOC ( diffSyntaxTerms term term ) ` shouldBe ` []
2017-02-14 22:29:24 +03:00
2017-02-23 07:05:20 +03:00
describe " JSONSummary " $ do
2017-06-05 18:32:18 +03:00
it " encodes modified summaries to JSON " $ do
2017-06-05 19:45:18 +03:00
let summary = JSONSummary " Method " " foo " ( sourceSpanBetween ( 1 , 1 ) ( 4 , 4 ) ) " modified "
2017-02-23 07:05:20 +03:00
encode summary ` shouldBe ` " { \ " span \ " :{ \ " start \ " :[1,1], \ " end \ " :[4,4]}, \ " category \ " : \ " Method \ " , \ " term \ " : \ " foo \ " , \ " changeType \ " : \ " modified \ " } "
2017-06-05 18:32:18 +03:00
it " encodes added summaries to JSON " $ do
2017-06-05 19:45:18 +03:00
let summary = JSONSummary " Method " " self.foo " ( sourceSpanBetween ( 1 , 1 ) ( 2 , 4 ) ) " added "
2017-02-23 07:05:20 +03:00
encode summary ` shouldBe ` " { \ " span \ " :{ \ " start \ " :[1,1], \ " end \ " :[2,4]}, \ " category \ " : \ " Method \ " , \ " term \ " : \ " self.foo \ " , \ " changeType \ " : \ " added \ " } "
2017-09-22 19:47:06 +03:00
describe " diff with ToCDiffRenderer' " $ do
2017-04-21 23:56:19 +03:00
it " produces JSON output " $ do
blobs <- blobsForPaths ( both " ruby/methods.A.rb " " ruby/methods.B.rb " )
2017-09-25 19:08:14 +03:00
output <- runTask ( diffBlobPair ToCDiffRenderer blobs )
2017-08-25 22:39:43 +03:00
toOutput output ` shouldBe ` ( " { \ " changes \ " :{ \ " test/fixtures/toc/ruby/methods.A.rb -> test/fixtures/toc/ruby/methods.B.rb \ " :[{ \ " span \ " :{ \ " start \ " :[1,1], \ " end \ " :[2,4]}, \ " category \ " : \ " Method \ " , \ " term \ " : \ " self.foo \ " , \ " changeType \ " : \ " modified \ " },{ \ " span \ " :{ \ " start \ " :[4,1], \ " end \ " :[6,4]}, \ " category \ " : \ " Method \ " , \ " term \ " : \ " bar \ " , \ " changeType \ " : \ " modified \ " }]}, \ " errors \ " :{}} \ n " :: ByteString )
2017-02-23 07:05:20 +03:00
2017-04-21 23:56:19 +03:00
it " produces JSON output if there are parse errors " $ do
blobs <- blobsForPaths ( both " ruby/methods.A.rb " " ruby/methods.X.rb " )
2017-09-25 19:08:14 +03:00
output <- runTask ( diffBlobPair ToCDiffRenderer blobs )
2017-09-15 02:32:45 +03:00
toOutput output ` shouldBe ` ( " { \ " changes \ " :{ \ " test/fixtures/toc/ruby/methods.A.rb -> test/fixtures/toc/ruby/methods.X.rb \ " :[{ \ " span \ " :{ \ " start \ " :[1,1], \ " end \ " :[2,4]}, \ " category \ " : \ " Method \ " , \ " term \ " : \ " bar \ " , \ " changeType \ " : \ " removed \ " },{ \ " span \ " :{ \ " start \ " :[4,1], \ " end \ " :[5,4]}, \ " category \ " : \ " Method \ " , \ " term \ " : \ " baz \ " , \ " changeType \ " : \ " removed \ " }]}, \ " errors \ " :{ \ " test/fixtures/toc/ruby/methods.A.rb -> test/fixtures/toc/ruby/methods.X.rb \ " :[{ \ " span \ " :{ \ " start \ " :[1,1], \ " end \ " :[3,1]}, \ " error \ " : \ " expected end of input nodes, but got ParseError \ " , \ " language \ " : \ " Ruby \ " }]}} \ n " :: ByteString )
2017-02-23 07:05:20 +03:00
2017-08-29 04:06:09 +03:00
it " ignores anonymous functions " $ do
blobs <- blobsForPaths ( both " ruby/lambda.A.rb " " ruby/lambda.B.rb " )
2017-09-25 19:08:14 +03:00
output <- runTask ( diffBlobPair ToCDiffRenderer blobs )
2017-08-29 04:06:09 +03:00
toOutput output ` shouldBe ` ( " { \ " changes \ " :{}, \ " errors \ " :{}} \ n " :: ByteString )
2017-02-23 07:05:20 +03:00
2017-07-10 22:54:03 +03:00
it " summarizes Markdown headings " $ do
blobs <- blobsForPaths ( both " markdown/headings.A.md " " markdown/headings.B.md " )
2017-09-25 19:08:14 +03:00
output <- runTask ( diffBlobPair ToCDiffRenderer blobs )
2017-08-14 18:51:55 +03:00
toOutput output ` shouldBe ` ( " { \ " changes \ " :{ \ " test/fixtures/toc/markdown/headings.A.md -> test/fixtures/toc/markdown/headings.B.md \ " :[{ \ " span \ " :{ \ " start \ " :[5,1], \ " end \ " :[7,10]}, \ " category \ " : \ " Heading 2 \ " , \ " term \ " : \ " Two \ " , \ " changeType \ " : \ " added \ " },{ \ " span \ " :{ \ " start \ " :[9,1], \ " end \ " :[10,4]}, \ " category \ " : \ " Heading 1 \ " , \ " term \ " : \ " Final \ " , \ " changeType \ " : \ " added \ " }]}, \ " errors \ " :{}} \ n " :: ByteString )
2017-07-10 22:54:03 +03:00
2017-09-14 16:41:52 +03:00
type Diff' = Diff Syntax ( Record ( Maybe Declaration ': DefaultFields ) ) ( Record ( Maybe Declaration ': DefaultFields ) )
2017-09-14 02:14:01 +03:00
type Term' = Term Syntax ( Record ( Maybe Declaration ': DefaultFields ) )
2017-02-17 01:20:22 +03:00
numTocSummaries :: Diff' -> Int
2017-07-20 03:01:59 +03:00
numTocSummaries diff = length $ filter isValidSummary ( diffTOC diff )
2017-02-17 01:20:22 +03:00
2017-02-17 02:41:13 +03:00
-- Return a diff where body is inserted in the expressions of a function. The function is present in both sides of the diff.
2017-02-17 02:22:46 +03:00
programWithChange :: Term' -> Diff'
2017-09-12 17:49:45 +03:00
programWithChange body = merge ( programInfo , programInfo ) ( Indexed [ function' ] )
2017-02-17 02:22:46 +03:00
where
2017-09-12 17:49:45 +03:00
function' = merge ( ( Just ( FunctionDeclaration " foo " ) :. functionInfo , Just ( FunctionDeclaration " foo " ) :. functionInfo ) ) ( S . Function name' [] [ inserting body ] )
name' = let info = Nothing :. Range 0 0 :. C . Identifier :. sourceSpanBetween ( 0 , 0 ) ( 0 , 0 ) :. Nil in merge ( info , info ) ( Leaf " foo " )
2017-02-17 02:41:13 +03:00
-- Return a diff where term is inserted in the program, below a function found on both sides of the diff.
programWithChangeOutsideFunction :: Term' -> Diff'
2017-09-12 17:49:45 +03:00
programWithChangeOutsideFunction term = merge ( programInfo , programInfo ) ( Indexed [ function' , term' ] )
2017-02-17 02:41:13 +03:00
where
2017-09-12 17:49:45 +03:00
function' = merge ( Just ( FunctionDeclaration " foo " ) :. functionInfo , Just ( FunctionDeclaration " foo " ) :. functionInfo ) ( S . Function name' [] [] )
name' = let info = Nothing :. Range 0 0 :. C . Identifier :. sourceSpanBetween ( 0 , 0 ) ( 0 , 0 ) :. Nil in merge ( info , info ) ( Leaf " foo " )
2017-05-10 23:08:39 +03:00
term' = inserting term
2017-02-17 02:22:46 +03:00
2017-05-08 22:08:01 +03:00
programWithInsert :: Text -> Term' -> Diff'
2017-05-11 20:49:25 +03:00
programWithInsert name body = programOf $ inserting ( functionOf name body )
2017-02-17 01:20:22 +03:00
2017-05-08 22:08:01 +03:00
programWithDelete :: Text -> Term' -> Diff'
2017-05-11 20:49:25 +03:00
programWithDelete name body = programOf $ deleting ( functionOf name body )
2017-02-16 23:23:40 +03:00
2017-05-08 22:08:01 +03:00
programWithReplace :: Text -> Term' -> Diff'
2017-05-11 20:49:25 +03:00
programWithReplace name body = programOf $ replacing ( functionOf name body ) ( functionOf ( name <> " 2 " ) body )
2017-02-16 23:23:40 +03:00
2017-05-11 20:49:25 +03:00
programOf :: Diff' -> Diff'
2017-09-12 17:49:45 +03:00
programOf diff = merge ( programInfo , programInfo ) ( Indexed [ diff ] )
2017-02-16 23:23:40 +03:00
2017-05-08 22:08:01 +03:00
functionOf :: Text -> Term' -> Term'
2017-09-11 22:48:58 +03:00
functionOf name body = Term $ ( Just ( FunctionDeclaration name ) :. functionInfo ) ` In ` S . Function name' [] [ body ]
2017-02-17 02:22:46 +03:00
where
2017-09-11 22:48:58 +03:00
name' = Term $ ( Nothing :. Range 0 0 :. C . Identifier :. sourceSpanBetween ( 0 , 0 ) ( 0 , 0 ) :. Nil ) ` In ` Leaf name
2017-02-16 03:13:34 +03:00
2017-05-11 22:53:22 +03:00
programInfo :: Record ( Maybe Declaration ': DefaultFields )
programInfo = Nothing :. Range 0 0 :. C . Program :. sourceSpanBetween ( 0 , 0 ) ( 0 , 0 ) :. Nil
2017-02-16 03:13:34 +03:00
2017-03-31 22:22:26 +03:00
functionInfo :: Record DefaultFields
2017-02-16 23:23:40 +03:00
functionInfo = Range 0 0 :. C . Function :. sourceSpanBetween ( 0 , 0 ) ( 0 , 0 ) :. Nil
2017-02-16 03:13:34 +03:00
2017-02-17 02:41:13 +03:00
-- Filter tiers for terms that we consider "meaniningful" in TOC summaries.
2017-09-09 16:18:08 +03:00
isMeaningfulTerm :: Term Syntax a -> Bool
isMeaningfulTerm a = case unTerm a of
2017-09-11 22:48:58 +03:00
( _ ` In ` S . Indexed _ ) -> False
( _ ` In ` S . Fixed _ ) -> False
( _ ` In ` S . Commented _ _ ) -> False
( _ ` In ` S . ParseError _ ) -> False
2017-02-17 02:22:46 +03:00
_ -> True
2017-02-16 03:13:34 +03:00
2017-02-17 02:41:13 +03:00
-- Filter tiers for terms if the Syntax is a Method or a Function.
2017-09-09 16:18:08 +03:00
isMethodOrFunction :: HasField fields Category => Term Syntax ( Record fields ) -> Bool
isMethodOrFunction a = case unTerm a of
2017-09-11 22:48:58 +03:00
( _ ` In ` S . Method { } ) -> True
( _ ` In ` S . Function { } ) -> True
( a ` In ` _ ) | getField a == C . Function -> True
( a ` In ` _ ) | getField a == C . Method -> True
( a ` In ` _ ) | getField a == C . SingletonMethod -> True
2017-02-17 02:41:13 +03:00
_ -> False
2017-06-24 17:15:31 +03:00
blobsForPaths :: Both FilePath -> IO ( Both Blob )
2017-05-10 01:49:38 +03:00
blobsForPaths = traverse ( readFile . ( " test/fixtures/toc/ " <> ) )
2017-02-14 22:29:24 +03:00
2017-06-24 16:30:34 +03:00
sourceSpanBetween :: ( Int , Int ) -> ( Int , Int ) -> Span
sourceSpanBetween ( s1 , e1 ) ( s2 , e2 ) = Span ( Pos s1 e1 ) ( Pos s2 e2 )
2017-02-14 22:29:24 +03:00
2017-05-11 22:53:22 +03:00
blankDiff :: Diff'
2017-09-12 17:49:45 +03:00
blankDiff = merge ( arrayInfo , arrayInfo ) ( Indexed [ inserting ( Term $ literalInfo ` In ` Leaf " \ " a \ " " ) ] )
2017-02-17 02:22:46 +03:00
where
2017-05-11 22:53:22 +03:00
arrayInfo = Nothing :. Range 0 3 :. ArrayLiteral :. sourceSpanBetween ( 1 , 1 ) ( 1 , 5 ) :. Nil
literalInfo = Nothing :. Range 1 2 :. StringLiteral :. sourceSpanBetween ( 1 , 2 ) ( 1 , 4 ) :. Nil
2017-02-14 22:29:24 +03:00
2017-06-24 17:15:31 +03:00
blankDiffBlobs :: Both Blob
blankDiffBlobs = both ( Blob ( fromText " [] " ) nullOid " a.js " ( Just defaultPlainBlob ) ( Just TypeScript ) ) ( Blob ( fromText " [a] " ) nullOid " b.js " ( Just defaultPlainBlob ) ( Just TypeScript ) )