mirror of
https://github.com/github/semantic.git
synced 2024-12-01 09:15:01 +03:00
Merge branch 'master' into generalize-alignment-over-the-syntax-functor
This commit is contained in:
commit
f14cd97cae
@ -1,5 +1,4 @@
|
||||
{-# LANGUAGE OverloadedStrings, TypeSynonymInstances, MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE DataKinds, GADTs, GeneralizedNewtypeDeriving, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
{-# LANGUAGE OverloadedStrings, TypeSynonymInstances, MultiParamTypeClasses, DataKinds, GADTs, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
module Renderer.JSON
|
||||
( json
|
||||
@ -10,15 +9,14 @@ module Renderer.JSON
|
||||
import Alignment
|
||||
import Data.Aeson (ToJSON, toJSON, encode, object, (.=))
|
||||
import Data.Aeson as A hiding (json)
|
||||
import Data.Aeson.Types (emptyArray)
|
||||
import Data.Bifunctor.Join
|
||||
import Data.Functor.Both
|
||||
import Data.Record
|
||||
import Data.These
|
||||
import Data.Vector as Vector hiding (toList)
|
||||
import Data.Vector as Vector
|
||||
import Diff
|
||||
import Info
|
||||
import Prologue
|
||||
import Prologue hiding ((++))
|
||||
import qualified Data.Map as Map
|
||||
import Source
|
||||
import SplitDiff
|
||||
@ -183,8 +181,13 @@ instance ToJSON a => ToJSON (File a) where
|
||||
toJSON File{..} = object [ "filePath" .= filePath, "programNode" .= fileContent ]
|
||||
|
||||
instance Monoid Value where
|
||||
mempty = emptyArray
|
||||
mappend a b = A.Array $ Vector.fromList [a, b]
|
||||
mempty = Null
|
||||
mappend a b | Null <- b = A.Array (singleton a)
|
||||
| Null <- a = A.Array (singleton b)
|
||||
| A.Array a' <- a, A.Array b' <- b = A.Array (a' ++ b')
|
||||
| A.Array b' <- b = A.Array (singleton a ++ b')
|
||||
| A.Array a' <- a = A.Array (a' ++ singleton b)
|
||||
| otherwise = A.Array (fromList [a, b])
|
||||
|
||||
instance StringConv Value ByteString where
|
||||
strConv _ = toS . (<> "\n") . encode
|
||||
|
@ -33,15 +33,18 @@ data ParseFixture = ParseFixture
|
||||
instance Listable ParseFixture where
|
||||
tiers = cons0 (ParseFixture (sExpressionParseTree pathMode "" []) sExpressionParseTreeOutput)
|
||||
\/ cons0 (ParseFixture (jsonParseTree pathMode "" []) jsonParseTreeOutput)
|
||||
\/ cons0 (ParseFixture (jsonParseTree pathMode' "" []) jsonParseTreeOutput')
|
||||
\/ cons0 (ParseFixture (sExpressionParseTree commitMode repo []) "(Program\n (Method\n (Identifier)))\n")
|
||||
\/ cons0 (ParseFixture (jsonParseTree commitMode repo []) "[{\"filePath\":\"methods.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"category\":\"Method\",\"identifier\":{\"category\":\"Identifier\",\"identifier\":\"foo\",\"range\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},\"clauses\":[],\"receiver\":null,\"range\":[0,11],\"callSignature\":[],\"definitions\":[],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,4]}}],\"range\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}}},[]]\n")
|
||||
\/ cons0 (ParseFixture (jsonParseTree commitMode repo []) "[{\"filePath\":\"methods.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"category\":\"Method\",\"identifier\":{\"category\":\"Identifier\",\"identifier\":\"foo\",\"range\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},\"clauses\":[],\"receiver\":null,\"range\":[0,11],\"callSignature\":[],\"definitions\":[],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,4]}}],\"range\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}}}]\n")
|
||||
|
||||
where
|
||||
pathMode = ParsePaths ["test/fixtures/ruby/and-or.A.rb"]
|
||||
pathMode' = ParsePaths ["test/fixtures/ruby/and-or.A.rb", "test/fixtures/ruby/and-or.B.rb"]
|
||||
commitMode = ParseCommit "2e4144eb8c44f007463ec34cb66353f0041161fe" ["methods.rb"]
|
||||
|
||||
sExpressionParseTreeOutput = "(Program\n (Binary\n (Identifier)\n (Other \"and\")\n (Identifier)))\n"
|
||||
jsonParseTreeOutput = "[{\"filePath\":\"test/fixtures/ruby/and-or.A.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"operatorSyntaxes\":[{\"category\":\"Identifier\",\"identifier\":\"foo\",\"range\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},{\"category\":\"and\",\"identifier\":\"and\",\"range\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},{\"category\":\"Identifier\",\"identifier\":\"bar\",\"range\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}}],\"category\":\"Binary\",\"range\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]}}],\"range\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]}}},[]]\n"
|
||||
jsonParseTreeOutput = "[{\"filePath\":\"test/fixtures/ruby/and-or.A.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"operatorSyntaxes\":[{\"category\":\"Identifier\",\"identifier\":\"foo\",\"range\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},{\"category\":\"and\",\"identifier\":\"and\",\"range\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},{\"category\":\"Identifier\",\"identifier\":\"bar\",\"range\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}}],\"category\":\"Binary\",\"range\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]}}],\"range\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]}}}]\n"
|
||||
jsonParseTreeOutput' = "[{\"filePath\":\"test/fixtures/ruby/and-or.A.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"operatorSyntaxes\":[{\"category\":\"Identifier\",\"identifier\":\"foo\",\"range\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},{\"category\":\"and\",\"identifier\":\"and\",\"range\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},{\"category\":\"Identifier\",\"identifier\":\"bar\",\"range\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}}],\"category\":\"Binary\",\"range\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]}}],\"range\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]}}},{\"filePath\":\"test/fixtures/ruby/and-or.B.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"operatorSyntaxes\":[{\"category\":\"Identifier\",\"identifier\":\"foo\",\"range\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},{\"category\":\"or\",\"identifier\":\"or\",\"range\":[4,6],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,7]}},{\"category\":\"Identifier\",\"identifier\":\"bar\",\"range\":[7,10],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]}}],\"category\":\"Binary\",\"range\":[0,10],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,11]}},{\"operatorSyntaxes\":[{\"operatorSyntaxes\":[{\"category\":\"Identifier\",\"identifier\":\"a\",\"range\":[11,12],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,2]}},{\"category\":\"or\",\"identifier\":\"or\",\"range\":[13,15],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,5]}},{\"category\":\"Identifier\",\"identifier\":\"b\",\"range\":[16,17],\"sourceSpan\":{\"start\":[2,6],\"end\":[2,7]}}],\"category\":\"Binary\",\"range\":[11,17],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,7]}},{\"category\":\"and\",\"identifier\":\"and\",\"range\":[18,21],\"sourceSpan\":{\"start\":[2,8],\"end\":[2,11]}},{\"category\":\"Identifier\",\"identifier\":\"c\",\"range\":[22,23],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]}}],\"category\":\"Binary\",\"range\":[11,23],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,13]}}],\"range\":[0,24],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}}}]\n"
|
||||
|
||||
|
||||
data DiffFixture = DiffFixture
|
||||
|
Loading…
Reference in New Issue
Block a user