1
1
mirror of https://github.com/github/semantic.git synced 2024-12-29 01:42:43 +03:00

Catch errors for some diff outputs

This commit is contained in:
Timothy Clem 2018-11-09 16:44:10 -08:00
parent 259479ad62
commit bc9f85fdef
4 changed files with 46 additions and 20 deletions

View File

@ -8,6 +8,7 @@ module Rendering.JSON
, renderJSONAST , renderJSONAST
, renderSymbolTerms , renderSymbolTerms
, renderJSONError , renderJSONError
, renderJSONDiffError
, SomeJSON(..) , SomeJSON(..)
) where ) where
@ -99,6 +100,10 @@ renderJSONError Blob{..} e = JSON [ SomeJSON (object [ "error" .= err ]) ]
, "path" .= blobPath , "path" .= blobPath
, "language" .= blobLanguage ] , "language" .= blobLanguage ]
renderJSONDiffError :: BlobPair -> String -> JSON "diffs" SomeJSON
renderJSONDiffError pair e = JSON [ SomeJSON (object [ "error" .= err ]) ]
where err = object ["message" .= e, "info" .= toJSON (JSONStat pair)]
data SomeJSON where data SomeJSON where
SomeJSON :: ToJSON a => a -> SomeJSON SomeJSON :: ToJSON a => a -> SomeJSON

View File

@ -14,6 +14,8 @@ module Rendering.Renderer
, renderToSymbols , renderToSymbols
, renderTreeGraph , renderTreeGraph
, renderJSONError , renderJSONError
, renderJSONDiffError
, renderJSONSummaryError
, Summaries(..) , Summaries(..)
, TOCSummary(..) , TOCSummary(..)
, SymbolFields(..) , SymbolFields(..)

View File

@ -3,6 +3,7 @@ module Rendering.TOC
( renderToCDiff ( renderToCDiff
, renderRPCToCDiff , renderRPCToCDiff
, renderToCTerm , renderToCTerm
, renderJSONSummaryError
, diffTOC , diffTOC
, Summaries(..) , Summaries(..)
, TOCSummary(..) , TOCSummary(..)
@ -31,6 +32,10 @@ import Data.Location
import Data.Term import Data.Term
import qualified Data.Text as T import qualified Data.Text as T
renderJSONSummaryError :: BlobPair -> String -> Summaries
renderJSONSummaryError pair e = Summaries mempty (Map.singleton "msg" [toJSON e]) -- JSON [ SomeJSON (object [ "error" .= err ]) ]
-- where err = object ["message" .= e, "info" .= toJSON (JSONStat pair)]
data Summaries = Summaries { changes, errors :: !(Map.Map T.Text [Value]) } data Summaries = Summaries { changes, errors :: !(Map.Map T.Text [Value]) }
deriving (Eq, Show) deriving (Eq, Show)

View File

@ -4,30 +4,31 @@ module Semantic.Diff
, diffBlobTOCPairs , diffBlobTOCPairs
) where ) where
import Analysis.ConstructorName (ConstructorName) import Analysis.ConstructorName (ConstructorName)
import Analysis.TOCSummary (HasDeclaration, declarationAlgebra) import Analysis.TOCSummary (HasDeclaration, declarationAlgebra)
import Control.Effect import Control.Effect
import Control.Monad.IO.Class import Control.Effect.Error
import Data.Blob import Control.Monad.IO.Class
import Data.Diff import Data.Blob
import Data.JSON.Fields import Data.Diff
import Data.Location import Data.Graph.DiffVertex
import Data.Term import Data.JSON.Fields
import Data.Graph.DiffVertex import Data.Location
import Diffing.Algorithm (Diffable) import Data.Term
import Parsing.Parser import Diffing.Algorithm (Diffable)
import Prologue import Parsing.Parser
import Rendering.Graph import Prologue
import Rendering.Renderer import Rendering.Graph
import Semantic.Telemetry as Stat import Rendering.JSON (SomeJSON (..))
import Semantic.Task as Task
import Serializing.Format
import Rendering.JSON (SomeJSON (..))
import qualified Rendering.JSON as JSON import qualified Rendering.JSON as JSON
import Rendering.Renderer
import Semantic.Task as Task
import Semantic.Telemetry as Stat
import Serializing.Format
-- | Using the specified renderer, diff a list of 'BlobPair's to produce a 'Builder' output. -- | Using the specified renderer, diff a list of 'BlobPair's to produce a 'Builder' output.
runDiff :: (Member Distribute sig, Member (Error SomeException) sig, Member Task sig, Member Telemetry sig, MonadIO m, Carrier sig m) => DiffRenderer output -> [BlobPair] -> m Builder runDiff :: (Member Distribute sig, Member (Error SomeException) sig, Member Task sig, Member Telemetry sig, MonadIO m, Carrier sig m) => DiffRenderer output -> [BlobPair] -> m Builder
runDiff ToCDiffRenderer = withParsedBlobPairs (decorate . declarationAlgebra) (render . renderToCDiff) >=> serialize JSON runDiff ToCDiffRenderer = withParsedBlobPairs' renderJSONSummaryError (decorate . declarationAlgebra) (render . renderToCDiff) >=> serialize JSON
runDiff JSONDiffRenderer = withParsedBlobPairs (const pure) (render . renderJSONDiff) >=> serialize JSON runDiff JSONDiffRenderer = withParsedBlobPairs (const pure) (render . renderJSONDiff) >=> serialize JSON
runDiff JSONGraphDiffRenderer = withParsedBlobPairs (const pure) (render . renderAdjGraph) >=> serialize JSON runDiff JSONGraphDiffRenderer = withParsedBlobPairs (const pure) (render . renderAdjGraph) >=> serialize JSON
where renderAdjGraph :: (Recursive t, ToTreeGraph DiffVertex (Base t)) => BlobPair -> t -> JSON.JSON "diffs" SomeJSON where renderAdjGraph :: (Recursive t, ToTreeGraph DiffVertex (Base t)) => BlobPair -> t -> JSON.JSON "diffs" SomeJSON
@ -48,6 +49,19 @@ diffBlobTOCPairs = withParsedBlobPairs (decorate . declarationAlgebra) (render .
type CanDiff syntax = (ConstructorName syntax, Diffable syntax, Eq1 syntax, HasDeclaration syntax, Hashable1 syntax, Show1 syntax, ToJSONFields1 syntax, Traversable syntax) type CanDiff syntax = (ConstructorName syntax, Diffable syntax, Eq1 syntax, HasDeclaration syntax, Hashable1 syntax, Show1 syntax, ToJSONFields1 syntax, Traversable syntax)
type Decorate m a b = forall syntax . CanDiff syntax => Blob -> Term syntax a -> m (Term syntax b) type Decorate m a b = forall syntax . CanDiff syntax => Blob -> Term syntax a -> m (Term syntax b)
withParsedBlobPairs' :: (Member Distribute sig, Member (Error SomeException) sig, Member Task sig, Member Telemetry sig, MonadIO m, Monoid output, Carrier sig m)
=> (BlobPair -> String -> output)
-> Decorate m Location ann
-> (forall syntax . CanDiff syntax => BlobPair -> Diff syntax ann ann -> m output)
-> [BlobPair]
-> m output
withParsedBlobPairs' onError decorate render = distributeFoldMap (\ blobs -> (withParsedBlobPair decorate blobs >>= withSomeTermPair (diffTerms blobs >=> render blobs)) `catchError` \(SomeException e) -> pure (onError blobs (show e)))
where diffTerms :: (Diffable syntax, Eq1 syntax, Hashable1 syntax, Traversable syntax, Member Task sig, Member Telemetry sig, Carrier sig m, MonadIO m) => BlobPair -> Join These (Term syntax ann) -> m (Diff syntax ann ann)
diffTerms blobs terms = time "diff" languageTag $ do
diff <- diff (runJoin terms)
diff <$ writeStat (Stat.count "diff.nodes" (bilength diff) languageTag)
where languageTag = languageTagForBlobPair blobs
withParsedBlobPairs :: (Member Distribute sig, Member (Error SomeException) sig, Member Task sig, Member Telemetry sig, MonadIO m, Monoid output, Carrier sig m) withParsedBlobPairs :: (Member Distribute sig, Member (Error SomeException) sig, Member Task sig, Member Telemetry sig, MonadIO m, Monoid output, Carrier sig m)
=> Decorate m Location ann => Decorate m Location ann
-> (forall syntax . CanDiff syntax => BlobPair -> Diff syntax ann ann -> m output) -> (forall syntax . CanDiff syntax => BlobPair -> Diff syntax ann ann -> m output)