1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 00:42:33 +03:00

Merge pull request #2157 from github/partial-results

Partial results
This commit is contained in:
Timothy Clem 2018-08-30 14:05:08 -07:00 committed by GitHub
commit bac8548f69
6 changed files with 72 additions and 30 deletions

View File

@ -36,8 +36,11 @@ service CodeAnalysis {
// Calculate an import graph for a project. // Calculate an import graph for a project.
rpc GraphImports (ImportGraphRequest) returns (ImportGraphResponse); rpc GraphImports (ImportGraphRequest) returns (ImportGraphResponse);
// Calculate a call graph for a project.
rpc GraphCalls (CallGraphRequest) returns (CallGraphResponse); rpc GraphCalls (CallGraphRequest) returns (CallGraphResponse);
// Status and Health
//
// Check health & status of the service. // Check health & status of the service.
rpc CheckHealth (HealthCheckRequest) returns (HealthCheckResponse); rpc CheckHealth (HealthCheckRequest) returns (HealthCheckResponse);
} }
@ -58,18 +61,22 @@ message ParseTreeResponse {
message RubyResponse { message RubyResponse {
repeated ruby_terms.RubyTerm terms = 1; repeated ruby_terms.RubyTerm terms = 1;
repeated DebugInfo errors = 2;
} }
message JSONResponse { message JSONResponse {
repeated json_terms.JSONTerm terms = 1; repeated json_terms.JSONTerm terms = 1;
repeated DebugInfo errors = 2;
} }
message TypeScriptResponse { message TypeScriptResponse {
repeated typescript_terms.TypeScriptTerm terms = 1; repeated typescript_terms.TypeScriptTerm terms = 1;
repeated DebugInfo errors = 2;
} }
message PythonResponse { message PythonResponse {
repeated python_terms.PythonTerm terms = 1; repeated python_terms.PythonTerm terms = 1;
repeated DebugInfo errors = 2;
} }
message SummarizeDiffRequest { message SummarizeDiffRequest {

View File

@ -5,6 +5,7 @@ module Rendering.JSON
, renderJSONTerm , renderJSONTerm
, renderJSONAST , renderJSONAST
, renderSymbolTerms , renderSymbolTerms
, renderJSONError
, SomeJSON(..) , SomeJSON(..)
) where ) where
@ -43,7 +44,6 @@ instance ToJSON JSONStat where
toJSON JSONStat{..} = object ("path" .= pathKeyForBlobPair jsonStatBlobs : toJSONFields (these Delete Insert Replace (runJoin jsonStatBlobs))) toJSON JSONStat{..} = object ("path" .= pathKeyForBlobPair jsonStatBlobs : toJSONFields (these Delete Insert Replace (runJoin jsonStatBlobs)))
toEncoding JSONStat{..} = pairs (fold ("path" .= pathKeyForBlobPair jsonStatBlobs : toJSONFields (these Delete Insert Replace (runJoin jsonStatBlobs)))) toEncoding JSONStat{..} = pairs (fold ("path" .= pathKeyForBlobPair jsonStatBlobs : toJSONFields (these Delete Insert Replace (runJoin jsonStatBlobs))))
-- | Render a term to a value representing its JSON. -- | Render a term to a value representing its JSON.
renderJSONTerm :: ToJSON a => Blob -> a -> JSON "trees" SomeJSON renderJSONTerm :: ToJSON a => Blob -> a -> JSON "trees" SomeJSON
renderJSONTerm blob content = JSON [ SomeJSON (JSONTerm blob content) ] renderJSONTerm blob content = JSON [ SomeJSON (JSONTerm blob content) ]
@ -71,6 +71,11 @@ instance ToJSON a => ToJSON (JSONAST a) where
renderSymbolTerms :: ToJSON a => [a] -> JSON "files" SomeJSON renderSymbolTerms :: ToJSON a => [a] -> JSON "files" SomeJSON
renderSymbolTerms = JSON . map SomeJSON renderSymbolTerms = JSON . map SomeJSON
renderJSONError :: Blob -> String -> JSON "trees" SomeJSON
renderJSONError Blob{..} e = JSON [ SomeJSON (object [ "error" .= err ]) ]
where err = object [ "message" .= e
, "path" .= blobPath
, "language" .= blobLanguage ]
data SomeJSON where data SomeJSON where
SomeJSON :: ToJSON a => a -> SomeJSON SomeJSON :: ToJSON a => a -> SomeJSON

View File

@ -11,6 +11,7 @@ module Rendering.Renderer
, renderSymbolTerms , renderSymbolTerms
, renderToSymbols , renderToSymbols
, renderTreeGraph , renderTreeGraph
, renderJSONError
, Summaries(..) , Summaries(..)
, TOCSummary(..) , TOCSummary(..)
, SymbolFields(..) , SymbolFields(..)

View File

@ -10,6 +10,7 @@ module Semantic.Parse
import Analysis.ConstructorName (ConstructorName) import Analysis.ConstructorName (ConstructorName)
import Analysis.Declaration (HasDeclaration, declarationAlgebra) import Analysis.Declaration (HasDeclaration, declarationAlgebra)
import Analysis.PackageDef (HasPackageDef) import Analysis.PackageDef (HasPackageDef)
import Control.Monad.Effect.Exception
import Data.AST import Data.AST
import Data.Blob import Data.Blob
import Data.JSON.Fields import Data.JSON.Fields
@ -29,34 +30,57 @@ import qualified Language.JSON.Assignment as JSON
import qualified Language.Python.Assignment as Python import qualified Language.Python.Assignment as Python
runParse :: (Member Distribute effs, Member (Exc SomeException) effs, Member Task effs) => TermRenderer output -> [Blob] -> Eff effs Builder runParse :: (Member Distribute effs, Member (Exc SomeException) effs, Member Task effs) => TermRenderer output -> [Blob] -> Eff effs Builder
runParse JSONTermRenderer = withParsedBlobs (render . renderJSONTerm) >=> serialize JSON runParse JSONTermRenderer = withParsedBlobs renderJSONError (render . renderJSONTerm) >=> serialize JSON
runParse SExpressionTermRenderer = withParsedBlobs (const (serialize (SExpression ByConstructorName))) runParse SExpressionTermRenderer = withParsedBlobs (\_ _ -> mempty) (const (serialize (SExpression ByConstructorName)))
runParse ShowTermRenderer = withParsedBlobs (const (serialize Show . quieterm)) runParse ShowTermRenderer = withParsedBlobs (\_ _ -> mempty) (const (serialize Show . quieterm))
runParse (SymbolsTermRenderer fields) = withParsedBlobs (\ blob -> decorate (declarationAlgebra blob) >=> render (renderSymbolTerms . renderToSymbols fields blob)) >=> serialize JSON runParse (SymbolsTermRenderer fields) = withParsedBlobs (\_ _ -> mempty) (\ blob -> decorate (declarationAlgebra blob) >=> render (renderSymbolTerms . renderToSymbols fields blob)) >=> serialize JSON
runParse DOTTermRenderer = withParsedBlobs (const (render renderTreeGraph)) >=> serialize (DOT (termStyle "terms")) runParse DOTTermRenderer = withParsedBlobs (\_ _ -> mempty) (const (render renderTreeGraph)) >=> serialize (DOT (termStyle "terms"))
runRubyParse :: (Member Distribute effs, Member Task effs) => [Blob] -> Eff effs [Term (Sum Ruby.Syntax) ()] -- NB: Our gRPC interface requires concrete 'Term's for each language to know
runRubyParse = flip distributeFor (\ blob -> do -- how to encode messages, so we have dedicated functions for parsing each
term <- parse rubyParser blob -- supported language.
pure (() <$ term)) runRubyParse :: (Member Distribute effs, Member (Exc SomeException) effs, Member Task effs)
=> [Blob] -> Eff effs [Either SomeException (Term (Sum Ruby.Syntax) ())]
runRubyParse = flip distributeFor $ \blob ->
(Right . (() <$) <$> parse rubyParser blob) `catchError` (pure . Left)
runTypeScriptParse :: (Member Distribute effs, Member Task effs) => [Blob] -> Eff effs [Term (Sum TypeScript.Syntax) ()] runTypeScriptParse :: (Member Distribute effs, Member (Exc SomeException) effs, Member Task effs)
runTypeScriptParse = flip distributeFor (\ blob -> do => [Blob] -> Eff effs [Either SomeException (Term (Sum TypeScript.Syntax) ())]
term <- parse typescriptParser blob runTypeScriptParse = flip distributeFor $ \blob -> do
pure (() <$ term)) (Right . (() <$) <$> parse typescriptParser blob) `catchError` (pure . Left)
runPythonParse :: (Member Distribute effs, Member Task effs) => [Blob] -> Eff effs [Term (Sum Python.Syntax) ()] runPythonParse :: (Member Distribute effs, Member (Exc SomeException) effs, Member Task effs)
runPythonParse = flip distributeFor (\ blob -> do => [Blob] -> Eff effs [Either SomeException (Term (Sum Python.Syntax) ())]
term <- parse pythonParser blob runPythonParse = flip distributeFor $ \blob -> do
pure (() <$ term)) (Right . (() <$) <$> parse pythonParser blob) `catchError` (pure . Left)
runJSONParse :: (Member Distribute effs, Member Task effs) => [Blob] -> Eff effs [Term (Sum JSON.Syntax) ()] runJSONParse :: (Member Distribute effs, Member (Exc SomeException) effs, Member Task effs)
runJSONParse = flip distributeFor (\ blob -> do => [Blob] -> Eff effs [Either SomeException (Term (Sum JSON.Syntax) ())]
term <- parse jsonParser blob runJSONParse = flip distributeFor $ \blob -> do
pure (() <$ term)) (Right . (() <$) <$> parse jsonParser blob) `catchError` (pure . Left)
withParsedBlobs :: (Member Distribute effs, Member (Exc SomeException) effs, Member Task effs, Monoid output) => (forall syntax . (ConstructorName syntax, Foldable syntax, Functor syntax, HasDeclaration syntax, HasPackageDef syntax, Show1 syntax, ToJSONFields1 syntax) => Blob -> Term syntax (Record Location) -> Eff effs output) -> [Blob] -> Eff effs output withParsedBlobs ::
withParsedBlobs render = distributeFoldMap (\ blob -> parseSomeBlob blob >>= withSomeTerm (render blob)) ( Member Distribute effs
, Member (Exc SomeException) effs
, Member Task effs
, Monoid output
)
=> (Blob -> String -> output)
-> ( forall syntax .
( ConstructorName syntax
, Foldable syntax
, Functor syntax
, HasDeclaration syntax
, HasPackageDef syntax
, Show1 syntax
, ToJSONFields1 syntax
) => Blob -> Term syntax (Record Location) -> Eff effs output
)
-> [Blob]
-> Eff effs output
withParsedBlobs onError render = distributeFoldMap $ \blob ->
(parseSomeBlob blob >>= withSomeTerm (render blob)) `catchError` \(SomeException e) ->
pure (onError blob (show e))
parseSomeBlob :: (Member (Exc SomeException) effs, Member Task effs) => Blob -> Eff effs (SomeTerm '[ConstructorName, Foldable, Functor, HasDeclaration, HasPackageDef, Show1, ToJSONFields1] (Record Location)) parseSomeBlob :: (Member (Exc SomeException) effs, Member Task effs) => Blob -> Eff effs (SomeTerm '[ConstructorName, Foldable, Functor, HasDeclaration, HasPackageDef, Show1, ToJSONFields1] (Record Location))
parseSomeBlob blob@Blob{..} = maybe (noLanguageForBlob blobPath) (`parse` blob) (someParser blobLanguage) parseSomeBlob blob@Blob{..} = maybe (noLanguageForBlob blobPath) (`parse` blob) (someParser blobLanguage)

View File

@ -65,6 +65,7 @@ import Data.Bool
import Data.ByteString.Builder import Data.ByteString.Builder
import Data.Diff import Data.Diff
import qualified Data.Error as Error import qualified Data.Error as Error
import Data.Language (Language)
import Data.Record import Data.Record
import Data.Source (Source) import Data.Source (Source)
import Data.Sum import Data.Sum
@ -195,7 +196,8 @@ runTaskF = interpret $ \ task -> case task of
logError :: Member Telemetry effs => Config -> Level -> Blob -> Error.Error String -> [(String, String)] -> Eff effs () logError :: Member Telemetry effs => Config -> Level -> Blob -> Error.Error String -> [(String, String)] -> Eff effs ()
logError Config{..} level blob err = writeLog level (Error.formatError configLogPrintSource configIsTerminal blob err) logError Config{..} level blob err = writeLog level (Error.formatError configLogPrintSource configIsTerminal blob err)
data ParserCancelled = ParserTimedOut deriving (Show, Typeable) data ParserCancelled = ParserTimedOut FilePath Language
deriving (Show, Typeable)
instance Exception ParserCancelled instance Exception ParserCancelled
@ -206,7 +208,7 @@ runParser blob@Blob{..} parser = case parser of
time "parse.tree_sitter_ast_parse" languageTag $ do time "parse.tree_sitter_ast_parse" languageTag $ do
config <- ask config <- ask
parseToAST (configTreeSitterParseTimeout config) language blob parseToAST (configTreeSitterParseTimeout config) language blob
>>= maybeM (throwError (SomeException ParserTimedOut)) >>= maybeM (throwError (SomeException (ParserTimedOut blobPath blobLanguage)))
AssignmentParser parser assignment -> runAssignment Assignment.assign parser assignment AssignmentParser parser assignment -> runAssignment Assignment.assign parser assignment
DeterministicParser parser assignment -> runAssignment Deterministic.assign parser assignment DeterministicParser parser assignment -> runAssignment Deterministic.assign parser assignment

View File

@ -11,10 +11,13 @@ import SpecHelpers
spec :: Spec spec :: Spec
spec = parallel $ do spec = parallel $ do
describe "parseBlob" $ do describe "parseBlob" $ do
it "throws if given an unknown language" $ do it "returns error if given an unknown language (json)" $ do
runTask (runParse SExpressionTermRenderer [methodsBlob { blobLanguage = Unknown }]) `shouldThrow` (\ code -> case code of output <- fmap runBuilder . runTask $ runParse JSONTermRenderer [ methodsBlob { blobLanguage = Unknown } ]
ExitFailure 1 -> True output `shouldBe` "{\"trees\":[{\"error\":{\"path\":\"methods.rb\",\"language\":\"Unknown\",\"message\":\"NoLanguageForBlob \\\"methods.rb\\\"\"}}]}\n"
_ -> False)
it "drops results for sexpression output" $ do
output <- fmap runBuilder . runTask $ runParse SExpressionTermRenderer [ methodsBlob { blobLanguage = Unknown } ]
output `shouldBe` ""
it "renders with the specified renderer" $ do it "renders with the specified renderer" $ do
output <- fmap runBuilder . runTask $ runParse SExpressionTermRenderer [methodsBlob] output <- fmap runBuilder . runTask $ runParse SExpressionTermRenderer [methodsBlob]