mirror of
https://github.com/github/semantic.git
synced 2024-12-27 00:44:57 +03:00
Merge remote-tracking branch 'origin/master' into indexer-prototype
This commit is contained in:
commit
f2aee684bc
29
notices/THIRD_PARTY_NOTICE.md
Normal file
29
notices/THIRD_PARTY_NOTICE.md
Normal file
@ -0,0 +1,29 @@
|
||||
# Third Party Notices and Information
|
||||
|
||||
Container images built with this project include third party materials; see
|
||||
below for license and other copyright information.
|
||||
|
||||
Certain open source code is available in container images, or online as noted
|
||||
below, or you may send a request for source code including identification of the
|
||||
container, the open source component name, and version number, to:
|
||||
`opensource@github.com`.
|
||||
|
||||
Notwithstanding any other terms, you may reverse engineer this software to the
|
||||
extent required to debug changes to any libraries licensed under the GNU Lesser
|
||||
General Public License for your own use.
|
||||
|
||||
## Debian packages
|
||||
|
||||
License and other copyright information for each package is included in the
|
||||
image at `/usr/share/doc/{package}/copyright`.
|
||||
|
||||
Source for each package is available at
|
||||
`https://packages.debian.org/source/{package}`.
|
||||
|
||||
## Haskell packages
|
||||
|
||||
License and other copyright information for each package is included in the
|
||||
image at `/usr/share/doc/licenses/cabal/{package}.txt`.
|
||||
|
||||
Source and additional information for each package is available at
|
||||
`https://hackage.haskell.org/package/{package}`.
|
@ -1,6 +1,6 @@
|
||||
cabal-version: 2.2
|
||||
name: semantic
|
||||
version: 0.5.0
|
||||
version: 0.6.0
|
||||
synopsis: Framework and service for analyzing and diffing untrusted code.
|
||||
description: Please see README.md
|
||||
homepage: http://github.com/github/semantic#readme
|
||||
|
@ -3,6 +3,7 @@ module Data.Language
|
||||
( Language (..)
|
||||
, SLanguage (..)
|
||||
, extensionsForLanguage
|
||||
, parseLanguage
|
||||
, knownLanguage
|
||||
, languageForFilePath
|
||||
, languageForType
|
||||
@ -80,20 +81,23 @@ instance Finite Language where
|
||||
go x = (fromString (fmap toUpper (show x)), fromEnum x)
|
||||
|
||||
instance FromJSON Language where
|
||||
parseJSON = withText "Language" $ \l -> pure $ case T.toLower l of
|
||||
"go" -> Go
|
||||
"haskell" -> Haskell
|
||||
"java" -> Java
|
||||
"javascript" -> JavaScript
|
||||
"json" -> JSON
|
||||
"jsx" -> JSX
|
||||
"markdown" -> Markdown
|
||||
"python" -> Python
|
||||
"ruby" -> Ruby
|
||||
"typescript" -> TypeScript
|
||||
"php" -> PHP
|
||||
_ -> Unknown
|
||||
parseJSON = withText "Language" $ \l ->
|
||||
pure $ fromMaybe Unknown (parseLanguage l)
|
||||
|
||||
parseLanguage :: Text -> Maybe Language
|
||||
parseLanguage l = case T.toLower l of
|
||||
"go" -> Just Go
|
||||
"haskell" -> Just Haskell
|
||||
"java" -> Just Java
|
||||
"javascript" -> Just JavaScript
|
||||
"json" -> Just JSON
|
||||
"jsx" -> Just JSX
|
||||
"markdown" -> Just Markdown
|
||||
"python" -> Just Python
|
||||
"ruby" -> Just Ruby
|
||||
"typescript" -> Just TypeScript
|
||||
"php" -> Just PHP
|
||||
_ -> Nothing
|
||||
|
||||
-- | Predicate failing on 'Unknown' and passing in all other cases.
|
||||
knownLanguage :: Language -> Bool
|
||||
|
@ -35,7 +35,6 @@ import Rendering.JSON hiding (JSON)
|
||||
import qualified Rendering.JSON
|
||||
import Semantic.Api.Helpers
|
||||
import Semantic.Api.V1.CodeAnalysisPB hiding (Blob, BlobPair, Language(..))
|
||||
import qualified Semantic.Api.V1.CodeAnalysisPB as API
|
||||
import Semantic.Task as Task
|
||||
import Semantic.Telemetry as Stat
|
||||
import Serializing.Format hiding (JSON)
|
||||
@ -51,9 +50,7 @@ data DiffOutputFormat
|
||||
|
||||
parseDiffBuilder :: (Traversable t, DiffEffects sig m) => DiffOutputFormat -> t BlobPair -> m Builder
|
||||
parseDiffBuilder DiffJSONTree = distributeFoldMap (jsonDiff renderJSONTree) >=> serialize Format.JSON -- NB: Serialize happens at the top level for these two JSON formats to collect results of multiple blob pairs.
|
||||
parseDiffBuilder DiffJSONGraph = distributeFoldMap (jsonDiff renderJSONGraph) >=> serialize Format.JSON
|
||||
-- TODO: Switch Diff Graph output on CLI to new format like this:
|
||||
-- parseDiffBuilder DiffJSONGraph = diffGraph >=> serialize Format.JSON
|
||||
parseDiffBuilder DiffJSONGraph = diffGraph >=> serialize Format.JSON
|
||||
parseDiffBuilder DiffSExpression = distributeFoldMap sexpDiff
|
||||
parseDiffBuilder DiffShow = distributeFoldMap showDiff
|
||||
parseDiffBuilder DiffDotGraph = distributeFoldMap dotGraphDiff
|
||||
@ -69,11 +66,8 @@ jsonError blobPair (SomeException e) = pure $ renderJSONDiffError blobPair (show
|
||||
renderJSONTree :: (Applicative m, ToJSONFields1 syntax) => BlobPair -> Diff syntax Location Location -> m (Rendering.JSON.JSON "diffs" SomeJSON)
|
||||
renderJSONTree blobPair = pure . renderJSONDiff blobPair
|
||||
|
||||
renderJSONGraph :: (Applicative m, Functor syntax, Foldable syntax, ConstructorName syntax) => BlobPair -> Diff syntax Location Location -> m (Rendering.JSON.JSON "diffs" SomeJSON)
|
||||
renderJSONGraph blobPair = pure . renderJSONAdjDiff blobPair . renderTreeGraph
|
||||
|
||||
diffGraph :: (Traversable t, DiffEffects sig m) => t API.BlobPair -> m DiffTreeGraphResponse
|
||||
diffGraph blobs = DiffTreeGraphResponse . V.fromList . toList <$> distributeFor (apiBlobPairToBlobPair <$> blobs) go
|
||||
diffGraph :: (Traversable t, DiffEffects sig m) => t BlobPair -> m DiffTreeGraphResponse
|
||||
diffGraph blobs = DiffTreeGraphResponse . V.fromList . toList <$> distributeFor blobs go
|
||||
where
|
||||
go :: (DiffEffects sig m) => BlobPair -> m DiffTreeFileGraph
|
||||
go blobPair = doDiff blobPair (const pure) render
|
||||
|
@ -3,10 +3,12 @@ module Semantic.Api.Helpers
|
||||
( spanToSpan
|
||||
, spanToLegacySpan
|
||||
, toChangeType
|
||||
, apiBlobToBlob
|
||||
, apiBlobPairToBlobPair
|
||||
, apiLanguageToLanguage
|
||||
, languageToApiLanguage
|
||||
, apiLanguageToLanguage
|
||||
, apiBlobsToBlobs
|
||||
, apiBlobToBlob
|
||||
, apiBlobPairsToBlobPairs
|
||||
, apiBlobPairToBlobPair
|
||||
) where
|
||||
|
||||
import Data.Bifunctor.Join
|
||||
@ -15,6 +17,7 @@ import qualified Data.Language as Data
|
||||
import Data.Source (fromText)
|
||||
import qualified Data.Span as Data
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Vector as V
|
||||
import Data.These
|
||||
import qualified Semantic.Api.LegacyTypes as Legacy
|
||||
import qualified Semantic.Api.V1.CodeAnalysisPB as API
|
||||
@ -34,8 +37,20 @@ toChangeType = \case
|
||||
"removed" -> API.Removed
|
||||
_ -> API.None
|
||||
|
||||
apiBlobToBlob :: API.Blob -> Data.Blob
|
||||
apiBlobToBlob API.Blob{..} = Data.Blob (fromText content) (T.unpack path) (apiLanguageToLanguage language)
|
||||
languageToApiLanguage :: Data.Language -> API.Language
|
||||
languageToApiLanguage = \case
|
||||
Data.Unknown -> API.Unknown
|
||||
Data.Go -> API.Go
|
||||
Data.Haskell -> API.Haskell
|
||||
Data.Java -> API.Java
|
||||
Data.JavaScript -> API.Javascript
|
||||
Data.JSON -> API.Json
|
||||
Data.JSX -> API.Jsx
|
||||
Data.Markdown -> API.Markdown
|
||||
Data.Python -> API.Python
|
||||
Data.Ruby -> API.Ruby
|
||||
Data.TypeScript -> API.Typescript
|
||||
Data.PHP -> API.Php
|
||||
|
||||
apiLanguageToLanguage :: API.Language -> Data.Language
|
||||
apiLanguageToLanguage = \case
|
||||
@ -52,20 +67,14 @@ apiLanguageToLanguage = \case
|
||||
API.Typescript -> Data.TypeScript
|
||||
API.Php -> Data.PHP
|
||||
|
||||
languageToApiLanguage :: Data.Language -> API.Language
|
||||
languageToApiLanguage = \case
|
||||
Data.Unknown -> API.Unknown
|
||||
Data.Go -> API.Go
|
||||
Data.Haskell -> API.Haskell
|
||||
Data.Java -> API.Java
|
||||
Data.JavaScript -> API.Javascript
|
||||
Data.JSON -> API.Json
|
||||
Data.JSX -> API.Jsx
|
||||
Data.Markdown -> API.Markdown
|
||||
Data.Python -> API.Python
|
||||
Data.Ruby -> API.Ruby
|
||||
Data.TypeScript -> API.Typescript
|
||||
Data.PHP -> API.Php
|
||||
apiBlobsToBlobs :: V.Vector API.Blob -> [Data.Blob]
|
||||
apiBlobsToBlobs = V.toList . fmap apiBlobToBlob
|
||||
|
||||
apiBlobToBlob :: API.Blob -> Data.Blob
|
||||
apiBlobToBlob API.Blob{..} = Data.Blob (fromText content) (T.unpack path) (apiLanguageToLanguage language)
|
||||
|
||||
apiBlobPairsToBlobPairs :: V.Vector API.BlobPair -> [Data.BlobPair]
|
||||
apiBlobPairsToBlobPairs = V.toList . fmap apiBlobPairToBlobPair
|
||||
|
||||
apiBlobPairToBlobPair :: API.BlobPair -> Data.BlobPair
|
||||
apiBlobPairToBlobPair (API.BlobPair (Just before) (Just after)) = Join (These (apiBlobToBlob before) (apiBlobToBlob after))
|
||||
|
@ -24,7 +24,6 @@ import Semantic.Api.Helpers
|
||||
import qualified Semantic.Api.LegacyTypes as Legacy
|
||||
import Semantic.Api.Terms (ParseEffects, doParse)
|
||||
import Semantic.Api.V1.CodeAnalysisPB hiding (Blob)
|
||||
import qualified Semantic.Api.V1.CodeAnalysisPB as API
|
||||
import Semantic.Task
|
||||
import Serializing.Format
|
||||
import Tags.Taggable
|
||||
@ -53,12 +52,10 @@ legacyParseSymbols blobs = Legacy.ParseTreeSymbolResponse <$> distributeFoldMap
|
||||
}
|
||||
|
||||
parseSymbolsBuilder :: (Member Distribute sig, ParseEffects sig m, Traversable t) => t Blob -> m Builder
|
||||
parseSymbolsBuilder blobs
|
||||
-- TODO: Switch away from legacy format on CLI too.
|
||||
= legacyParseSymbols blobs >>= serialize JSON
|
||||
parseSymbolsBuilder blobs = parseSymbols blobs >>= serialize JSON
|
||||
|
||||
parseSymbols :: (Member Distribute sig, ParseEffects sig m, Traversable t) => t API.Blob -> m ParseTreeSymbolResponse
|
||||
parseSymbols blobs = ParseTreeSymbolResponse . V.fromList . toList <$> distributeFor (apiBlobToBlob <$> blobs) go
|
||||
parseSymbols :: (Member Distribute sig, ParseEffects sig m, Traversable t) => t Blob -> m ParseTreeSymbolResponse
|
||||
parseSymbols blobs = ParseTreeSymbolResponse . V.fromList . toList <$> distributeFor blobs go
|
||||
where
|
||||
go :: (Member (Error SomeException) sig, Member Task sig, Carrier sig m, Monad m) => Blob -> m File
|
||||
go blob@Blob{..} = (doParse blob >>= withSomeTerm (renderToSymbols blob)) `catchError` (\(SomeException e) -> pure $ errorFile (show e))
|
||||
|
@ -15,14 +15,11 @@ import Rendering.TOC
|
||||
import Semantic.Api.Diffs
|
||||
import Semantic.Api.Helpers
|
||||
import Semantic.Api.V1.CodeAnalysisPB hiding (Blob, BlobPair)
|
||||
import qualified Semantic.Api.V1.CodeAnalysisPB as API
|
||||
import Semantic.Task as Task
|
||||
import Serializing.Format
|
||||
|
||||
diffSummaryBuilder :: (DiffEffects sig m) => Format Summaries -> [BlobPair] -> m Builder
|
||||
diffSummaryBuilder format blobs
|
||||
-- TODO: Switch away from legacy format on CLI too.
|
||||
= legacyDiffSummary blobs >>= serialize format
|
||||
diffSummaryBuilder :: (DiffEffects sig m) => Format DiffTreeTOCResponse -> [BlobPair] -> m Builder
|
||||
diffSummaryBuilder format blobs = diffSummary blobs >>= serialize format
|
||||
|
||||
legacyDiffSummary :: (DiffEffects sig m) => [BlobPair] -> m Summaries
|
||||
legacyDiffSummary = distributeFoldMap go
|
||||
@ -37,8 +34,8 @@ legacyDiffSummary = distributeFoldMap go
|
||||
render :: (Foldable syntax, Functor syntax, Applicative m) => BlobPair -> Diff syntax (Maybe Declaration) (Maybe Declaration) -> m Summaries
|
||||
render blobPair = pure . renderToCDiff blobPair
|
||||
|
||||
diffSummary :: (DiffEffects sig m) => [API.BlobPair] -> m DiffTreeTOCResponse
|
||||
diffSummary blobs = DiffTreeTOCResponse . V.fromList <$> distributeFor (apiBlobPairToBlobPair <$> blobs) go
|
||||
diffSummary :: (DiffEffects sig m) => [BlobPair] -> m DiffTreeTOCResponse
|
||||
diffSummary blobs = DiffTreeTOCResponse . V.fromList <$> distributeFor blobs go
|
||||
where
|
||||
go :: (DiffEffects sig m) => BlobPair -> m TOCSummaryFile
|
||||
go blobPair = doDiff blobPair (decorate . declarationAlgebra) render
|
||||
|
@ -38,14 +38,13 @@ import Rendering.JSON hiding (JSON)
|
||||
import qualified Rendering.JSON
|
||||
import Semantic.Api.Helpers
|
||||
import Semantic.Api.V1.CodeAnalysisPB hiding (Blob, Language (..))
|
||||
import qualified Semantic.Api.V1.CodeAnalysisPB as API
|
||||
import Semantic.Task
|
||||
import Serializing.Format hiding (JSON)
|
||||
import qualified Serializing.Format as Format
|
||||
import Tags.Taggable
|
||||
|
||||
termGraph :: (Traversable t, Member Distribute sig, ParseEffects sig m) => t API.Blob -> m ParseTreeGraphResponse
|
||||
termGraph blobs = ParseTreeGraphResponse . V.fromList . toList <$> distributeFor (fmap apiBlobToBlob blobs) go
|
||||
termGraph :: (Traversable t, Member Distribute sig, ParseEffects sig m) => t Blob -> m ParseTreeGraphResponse
|
||||
termGraph blobs = ParseTreeGraphResponse . V.fromList . toList <$> distributeFor blobs go
|
||||
where
|
||||
go :: ParseEffects sig m => Blob -> m ParseTreeFileGraph
|
||||
go blob = (doParse blob >>= withSomeTerm (pure . render))
|
||||
@ -72,9 +71,7 @@ data TermOutputFormat
|
||||
parseTermBuilder :: (Traversable t, Member Distribute sig, ParseEffects sig m, MonadIO m)
|
||||
=> TermOutputFormat-> t Blob -> m Builder
|
||||
parseTermBuilder TermJSONTree = distributeFoldMap jsonTerm >=> serialize Format.JSON -- NB: Serialize happens at the top level for these two JSON formats to collect results of multiple blobs.
|
||||
parseTermBuilder TermJSONGraph = distributeFoldMap jsonGraph >=> serialize Format.JSON -- termGraph >=> serialize Format.JSON
|
||||
-- TODO: Switch Term Graph output on CLI to new format like this:
|
||||
-- parseTermBuilder TermJSONGraph = termGraph >=> serialize Format.JSON
|
||||
parseTermBuilder TermJSONGraph = termGraph >=> serialize Format.JSON
|
||||
parseTermBuilder TermSExpression = distributeFoldMap sexpTerm
|
||||
parseTermBuilder TermDotGraph = distributeFoldMap dotGraphTerm
|
||||
parseTermBuilder TermShow = distributeFoldMap showTerm
|
||||
@ -83,9 +80,6 @@ parseTermBuilder TermQuiet = distributeFoldMap quietTerm
|
||||
jsonTerm :: (ParseEffects sig m) => Blob -> m (Rendering.JSON.JSON "trees" SomeJSON)
|
||||
jsonTerm blob = (doParse blob >>= withSomeTerm (pure . renderJSONTerm blob)) `catchError` jsonError blob
|
||||
|
||||
jsonGraph :: (ParseEffects sig m) => Blob -> m (Rendering.JSON.JSON "trees" SomeJSON)
|
||||
jsonGraph blob = (doParse blob >>= withSomeTerm (pure . renderJSONAdjTerm blob . renderTreeGraph)) `catchError` jsonError blob
|
||||
|
||||
jsonError :: Applicative m => Blob -> SomeException -> m (Rendering.JSON.JSON "trees" SomeJSON)
|
||||
jsonError blob (SomeException e) = pure $ renderJSONError blob (show e)
|
||||
|
||||
|
@ -3,11 +3,12 @@ module Semantic.CLI (main) where
|
||||
|
||||
import Control.Exception as Exc (displayException)
|
||||
import Data.File
|
||||
import Data.Language (languageForFilePath)
|
||||
import Data.Handle
|
||||
import Data.Language (languageForFilePath, parseLanguage)
|
||||
import Data.List (intercalate, uncons)
|
||||
import Data.List.Split (splitWhen)
|
||||
import Data.Handle
|
||||
import Data.Project
|
||||
import qualified Data.Text as T
|
||||
import Options.Applicative hiding (style)
|
||||
import Prologue
|
||||
import Semantic.Api hiding (File)
|
||||
@ -15,14 +16,13 @@ import qualified Semantic.AST as AST
|
||||
import Semantic.Config
|
||||
import qualified Semantic.Graph as Graph
|
||||
import qualified Semantic.Task as Task
|
||||
import qualified Semantic.Telemetry.Log as Log
|
||||
import Semantic.Task.Files
|
||||
import Semantic.Telemetry
|
||||
import qualified Semantic.Telemetry.Log as Log
|
||||
import Semantic.Version
|
||||
import Serializing.Format hiding (Options)
|
||||
import System.Exit (die)
|
||||
import System.FilePath
|
||||
import Serializing.Format hiding (Options)
|
||||
import Text.Read
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
@ -60,12 +60,12 @@ diffCommand :: Mod CommandFields (Task.TaskEff Builder)
|
||||
diffCommand = command "diff" (info diffArgumentsParser (progDesc "Compute changes between paths"))
|
||||
where
|
||||
diffArgumentsParser = do
|
||||
renderer <- flag (parseDiffBuilder DiffSExpression) (parseDiffBuilder DiffSExpression) (long "sexpression" <> help "Output s-expression diff tree (default)")
|
||||
<|> flag' (parseDiffBuilder DiffJSONTree) (long "json" <> help "Output JSON diff trees")
|
||||
<|> flag' (parseDiffBuilder DiffJSONGraph) (long "json-graph" <> help "Output JSON diff trees")
|
||||
<|> flag' (diffSummaryBuilder JSON) (long "toc" <> help "Output JSON table of contents diff summary")
|
||||
<|> flag' (parseDiffBuilder DiffDotGraph) (long "dot" <> help "Output the diff as a DOT graph")
|
||||
<|> flag' (parseDiffBuilder DiffShow) (long "show" <> help "Output using the Show instance (debug only, format subject to change without notice)")
|
||||
renderer <- flag (parseDiffBuilder DiffSExpression) (parseDiffBuilder DiffSExpression) (long "sexpression" <> help "Output s-expression diff tree (default)")
|
||||
<|> flag' (parseDiffBuilder DiffJSONTree) (long "json" <> help "Output JSON diff trees")
|
||||
<|> flag' (parseDiffBuilder DiffJSONGraph) (long "json-graph" <> help "Output JSON diff trees")
|
||||
<|> flag' (diffSummaryBuilder JSON) (long "toc" <> help "Output JSON table of contents diff summary")
|
||||
<|> flag' (parseDiffBuilder DiffDotGraph) (long "dot" <> help "Output the diff as a DOT graph")
|
||||
<|> flag' (parseDiffBuilder DiffShow) (long "show" <> help "Output using the Show instance (debug only, format subject to change without notice)")
|
||||
filesOrStdin <- Right <$> some (Both <$> argument filePathReader (metavar "FILE_A") <*> argument filePathReader (metavar "FILE_B")) <|> pure (Left stdin)
|
||||
pure $ Task.readBlobPairs filesOrStdin >>= renderer
|
||||
|
||||
@ -77,9 +77,9 @@ parseCommand = command "parse" (info parseArgumentsParser (progDesc "Generate pa
|
||||
<|> flag' (parseTermBuilder TermJSONTree) (long "json" <> help "Output JSON parse trees")
|
||||
<|> flag' (parseTermBuilder TermJSONGraph) (long "json-graph" <> help "Output JSON adjacency list")
|
||||
<|> flag' parseSymbolsBuilder (long "symbols" <> help "Output JSON symbol list")
|
||||
<|> flag' (parseTermBuilder TermDotGraph) (long "dot" <> help "Output DOT graph parse trees")
|
||||
<|> flag' (parseTermBuilder TermShow) (long "show" <> help "Output using the Show instance (debug only, format subject to change without notice)")
|
||||
<|> flag' (parseTermBuilder TermQuiet) (long "quiet" <> help "Don't produce output, but show timing stats")
|
||||
<|> flag' (parseTermBuilder TermDotGraph) (long "dot" <> help "Output DOT graph parse trees")
|
||||
<|> flag' (parseTermBuilder TermShow) (long "show" <> help "Output using the Show instance (debug only, format subject to change without notice)")
|
||||
<|> flag' (parseTermBuilder TermQuiet) (long "quiet" <> help "Don't produce output, but show timing stats")
|
||||
filesOrStdin <- Right <$> some (argument filePathReader (metavar "FILES...")) <|> pure (Left stdin)
|
||||
pure $ Task.readBlobs filesOrStdin >>= renderer
|
||||
|
||||
@ -126,10 +126,10 @@ filePathReader :: ReadM File
|
||||
filePathReader = eitherReader parseFilePath
|
||||
where
|
||||
parseFilePath arg = case splitWhen (== ':') arg of
|
||||
[a, b] | Just lang <- readMaybe a -> Right (File a lang)
|
||||
| Just lang <- readMaybe b -> Right (File b lang)
|
||||
[a, b] | Just lang <- parseLanguage (T.pack b) -> Right (File a lang)
|
||||
| Just lang <- parseLanguage (T.pack a) -> Right (File b lang)
|
||||
[path] -> Right (File path (languageForFilePath path))
|
||||
args -> Left ("cannot parse `" <> join args <> "`\nexpecting FILE:LANGUAGE or just FILE")
|
||||
_ -> Left ("cannot parse `" <> arg <> "`\nexpecting FILE:LANGUAGE or just FILE")
|
||||
|
||||
options :: Eq a => [(String, a)] -> Mod OptionFields a -> Parser a
|
||||
options options fields = option (optionsReader options) (fields <> showDefaultWith (findOption options) <> metavar (intercalate "|" (fmap fst options)))
|
||||
|
@ -149,22 +149,22 @@ spec = parallel $ do
|
||||
it "produces JSON output" $ do
|
||||
blobs <- blobsForPaths (Both "ruby/toc/methods.A.rb" "ruby/toc/methods.B.rb")
|
||||
output <- runTaskOrDie (diffSummaryBuilder Format.JSON [blobs])
|
||||
runBuilder output `shouldBe` ("{\"changes\":{\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.B.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"},{\"span\":{\"start\":[4,1],\"end\":[6,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"modified\"},{\"span\":{\"start\":[4,1],\"end\":[5,4]},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"removed\"}]},\"errors\":{}}\n" :: ByteString)
|
||||
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.B.rb\",\"changes\":[{\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":2,\"column\":4}},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"Added\"},{\"span\":{\"start\":{\"line\":4,\"column\":1},\"end\":{\"line\":6,\"column\":4}},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"Modified\"},{\"span\":{\"start\":{\"line\":4,\"column\":1},\"end\":{\"line\":5,\"column\":4}},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"Removed\"}],\"language\":\"Ruby\",\"errors\":[]}]}\n" :: ByteString)
|
||||
|
||||
it "produces JSON output if there are parse errors" $ do
|
||||
blobs <- blobsForPaths (Both "ruby/toc/methods.A.rb" "ruby/toc/methods.X.rb")
|
||||
output <- runTaskOrDie (diffSummaryBuilder Format.JSON [blobs])
|
||||
runBuilder output `shouldBe` ("{\"changes\":{\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/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/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.X.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,3]},\"error\":\"expected end of input nodes, but got ParseError\",\"language\":\"Ruby\"}]}}\n" :: ByteString)
|
||||
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.X.rb\",\"changes\":[{\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":2,\"column\":4}},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"Removed\"},{\"span\":{\"start\":{\"line\":4,\"column\":1},\"end\":{\"line\":5,\"column\":4}},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"Removed\"}],\"language\":\"Ruby\",\"errors\":[{\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":2,\"column\":3}},\"error\":\"expected end of input nodes, but got ParseError\"}]}]}\n" :: ByteString)
|
||||
|
||||
it "ignores anonymous functions" $ do
|
||||
blobs <- blobsForPaths (Both "ruby/toc/lambda.A.rb" "ruby/toc/lambda.B.rb")
|
||||
output <- runTaskOrDie (diffSummaryBuilder Format.JSON [blobs])
|
||||
runBuilder output `shouldBe` ("{\"changes\":{},\"errors\":{}}\n" :: ByteString)
|
||||
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/ruby/toc/lambda.A.rb -> test/fixtures/ruby/toc/lambda.B.rb\",\"changes\":[],\"language\":\"Ruby\",\"errors\":[]}]}\n" :: ByteString)
|
||||
|
||||
it "summarizes Markdown headings" $ do
|
||||
blobs <- blobsForPaths (Both "markdown/toc/headings.A.md" "markdown/toc/headings.B.md")
|
||||
output <- runTaskOrDie (diffSummaryBuilder Format.JSON [blobs])
|
||||
runBuilder output `shouldBe` ("{\"changes\":{\"test/fixtures/markdown/toc/headings.A.md -> test/fixtures/markdown/toc/headings.B.md\":[{\"span\":{\"start\":[1,1],\"end\":[3,16]},\"category\":\"Heading 1\",\"term\":\"Introduction\",\"changeType\":\"removed\"},{\"span\":{\"start\":[5,1],\"end\":[7,4]},\"category\":\"Heading 2\",\"term\":\"Two\",\"changeType\":\"modified\"},{\"span\":{\"start\":[9,1],\"end\":[11,10]},\"category\":\"Heading 3\",\"term\":\"This heading is new\",\"changeType\":\"added\"},{\"span\":{\"start\":[13,1],\"end\":[14,4]},\"category\":\"Heading 1\",\"term\":\"Final\",\"changeType\":\"added\"}]},\"errors\":{}}\n" :: ByteString)
|
||||
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/markdown/toc/headings.A.md -> test/fixtures/markdown/toc/headings.B.md\",\"changes\":[{\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":3,\"column\":16}},\"category\":\"Heading 1\",\"term\":\"Introduction\",\"changeType\":\"Removed\"},{\"span\":{\"start\":{\"line\":5,\"column\":1},\"end\":{\"line\":7,\"column\":4}},\"category\":\"Heading 2\",\"term\":\"Two\",\"changeType\":\"Modified\"},{\"span\":{\"start\":{\"line\":9,\"column\":1},\"end\":{\"line\":11,\"column\":10}},\"category\":\"Heading 3\",\"term\":\"This heading is new\",\"changeType\":\"Added\"},{\"span\":{\"start\":{\"line\":13,\"column\":1},\"end\":{\"line\":14,\"column\":4}},\"category\":\"Heading 1\",\"term\":\"Final\",\"changeType\":\"Added\"}],\"language\":\"Markdown\",\"errors\":[]}]}\n" :: ByteString)
|
||||
|
||||
|
||||
type Diff' = Diff ListableSyntax (Maybe Declaration) (Maybe Declaration)
|
||||
|
27
test/fixtures/cli/diff-tree.toc.json
vendored
27
test/fixtures/cli/diff-tree.toc.json
vendored
@ -1,18 +1,27 @@
|
||||
{
|
||||
"changes":
|
||||
"files": [
|
||||
{
|
||||
"test/fixtures/ruby/corpus/method-declaration.A.rb -> test/fixtures/ruby/corpus/method-declaration.B.rb": [
|
||||
"path": "test/fixtures/ruby/corpus/method-declaration.A.rb -> test/fixtures/ruby/corpus/method-declaration.B.rb",
|
||||
"changes": [
|
||||
{
|
||||
"span":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [3, 4]
|
||||
"start":
|
||||
{
|
||||
"line": 1,
|
||||
"column": 1
|
||||
},
|
||||
"end":
|
||||
{
|
||||
"line": 3,
|
||||
"column": 4
|
||||
}
|
||||
},
|
||||
"category": "Method",
|
||||
"term": "bar",
|
||||
"changeType": "modified"
|
||||
}]
|
||||
},
|
||||
"errors":
|
||||
{}
|
||||
"changeType": "Modified"
|
||||
}],
|
||||
"language": "Ruby",
|
||||
"errors": []
|
||||
}]
|
||||
}
|
||||
|
18
test/fixtures/cli/parse-tree.symbols.json
vendored
18
test/fixtures/cli/parse-tree.symbols.json
vendored
@ -6,13 +6,23 @@
|
||||
{
|
||||
"span":
|
||||
{
|
||||
"start": [1, 1],
|
||||
"end": [2, 4]
|
||||
"start":
|
||||
{
|
||||
"line": 1,
|
||||
"column": 1
|
||||
},
|
||||
"end":
|
||||
{
|
||||
"line": 2,
|
||||
"column": 4
|
||||
}
|
||||
},
|
||||
"kind": "Method",
|
||||
"symbol": "foo",
|
||||
"line": "def foo"
|
||||
"line": "def foo",
|
||||
"docs": null
|
||||
}],
|
||||
"language": "Ruby"
|
||||
"language": "Ruby",
|
||||
"errors": []
|
||||
}]
|
||||
}
|
||||
|
Loading…
Reference in New Issue
Block a user