1
1
mirror of https://github.com/github/semantic.git synced 2024-11-27 12:57:49 +03:00

Better handling of partial errors

This commit is contained in:
Timothy Clem 2019-02-05 10:04:37 -08:00
parent 2cb4d44f4a
commit 3de377b6da
4 changed files with 35 additions and 8 deletions

View File

@ -75,12 +75,14 @@ diffGraph blobs = distributeFoldMap go (apiBlobPairToBlobPair <$> blobs)
where where
go :: (DiffEffects sig m) => BlobPair -> m DiffTreeGraphResponse go :: (DiffEffects sig m) => BlobPair -> m DiffTreeGraphResponse
go blobPair = doDiff blobPair (const pure) render go blobPair = doDiff blobPair (const pure) render
`catchError` \(SomeException e) ->
pure (DiffTreeGraphResponse mempty mempty [ParseError (pathForBlobPair blobPair) (show e)])
render :: (Foldable syntax, Functor syntax, ConstructorName syntax, Applicative m) => BlobPair -> Diff syntax Location Location -> m DiffTreeGraphResponse render :: (Foldable syntax, Functor syntax, ConstructorName syntax, Applicative m) => BlobPair -> Diff syntax Location Location -> m DiffTreeGraphResponse
render _ diff = render _ diff =
let graph = renderTreeGraph diff let graph = renderTreeGraph diff
toEdge (Edge (a, b)) = DiffTreeEdge (diffVertexId a) (diffVertexId b) toEdge (Edge (a, b)) = DiffTreeEdge (diffVertexId a) (diffVertexId b)
in pure $ DiffTreeGraphResponse (vertexList graph) (fmap toEdge (edgeList graph)) in pure $ DiffTreeGraphResponse (vertexList graph) (fmap toEdge (edgeList graph)) mempty
sexpDiff :: (DiffEffects sig m) => BlobPair -> m Builder sexpDiff :: (DiffEffects sig m) => BlobPair -> m Builder

View File

@ -2,9 +2,13 @@
module Semantic.API.TOCSummaries (diffSummary, legacyDiffSummary, diffSummaryBuilder) where module Semantic.API.TOCSummaries (diffSummary, legacyDiffSummary, diffSummaryBuilder) where
import Analysis.TOCSummary (Declaration, declarationAlgebra) import Analysis.TOCSummary (Declaration, declarationAlgebra)
import Control.Effect.Error
import Data.Aeson
import Data.Blob import Data.Blob
import Data.ByteString.Builder import Data.ByteString.Builder
import Data.Diff import Data.Diff
import qualified Data.Map.Monoidal as Map
import Data.Span (emptySpan)
import qualified Data.Text as T import qualified Data.Text as T
import Rendering.TOC import Rendering.TOC
import Semantic.API.Diffs import Semantic.API.Diffs
@ -24,6 +28,10 @@ legacyDiffSummary = distributeFoldMap go
where where
go :: (DiffEffects sig m) => BlobPair -> m Summaries go :: (DiffEffects sig m) => BlobPair -> m Summaries
go blobPair = doDiff blobPair (decorate . declarationAlgebra) render go blobPair = doDiff blobPair (decorate . declarationAlgebra) render
`catchError` \(SomeException e) ->
pure $ Summaries mempty (Map.singleton path [toJSON (ErrorSummary (T.pack (show e)) emptySpan lang)])
where path = T.pack $ pathKeyForBlobPair blobPair
lang = languageForBlobPair blobPair
render :: (Foldable syntax, Functor syntax, Applicative m) => BlobPair -> Diff syntax (Maybe Declaration) (Maybe Declaration) -> m Summaries render :: (Foldable syntax, Functor syntax, Applicative m) => BlobPair -> Diff syntax (Maybe Declaration) (Maybe Declaration) -> m Summaries
render blobPair = pure . renderToCDiff blobPair render blobPair = pure . renderToCDiff blobPair
@ -33,6 +41,10 @@ diffSummary blobs = DiffTreeTOCResponse <$> distributeFor (apiBlobPairToBlobPair
where where
go :: (DiffEffects sig m) => BlobPair -> m TOCSummaryFile go :: (DiffEffects sig m) => BlobPair -> m TOCSummaryFile
go blobPair = doDiff blobPair (decorate . declarationAlgebra) render go blobPair = doDiff blobPair (decorate . declarationAlgebra) render
`catchError` \(SomeException e) ->
pure $ TOCSummaryFile path lang mempty [TOCSummaryError (T.pack (show e)) Nothing]
where path = T.pack $ pathKeyForBlobPair blobPair
lang = languageForBlobPair blobPair
render :: (Foldable syntax, Functor syntax, Applicative m) => BlobPair -> Diff syntax (Maybe Declaration) (Maybe Declaration) -> m TOCSummaryFile render :: (Foldable syntax, Functor syntax, Applicative m) => BlobPair -> Diff syntax (Maybe Declaration) (Maybe Declaration) -> m TOCSummaryFile
render blobPair diff = pure $ foldr go (TOCSummaryFile path lang mempty mempty) (diffTOC diff) render blobPair diff = pure $ foldr go (TOCSummaryFile path lang mempty mempty) (diffTOC diff)
@ -45,3 +57,8 @@ diffSummary blobs = DiffTreeTOCResponse <$> distributeFor (apiBlobPairToBlobPair
= TOCSummaryFile path language (TOCSummaryChange summaryCategoryName summaryTermName (spanToSpan summarySpan) (toChangeType summaryChangeType) : changes) errors = TOCSummaryFile path language (TOCSummaryChange summaryCategoryName summaryTermName (spanToSpan summarySpan) (toChangeType summaryChangeType) : changes) errors
go ErrorSummary{..} TOCSummaryFile{..} go ErrorSummary{..} TOCSummaryFile{..}
= TOCSummaryFile path language changes (TOCSummaryError errorText (spanToSpan errorSpan) : errors) = TOCSummaryFile path language changes (TOCSummaryError errorText (spanToSpan errorSpan) : errors)
fileError :: BlobPair -> String -> TOCSummaryFile
fileError blobPair e = TOCSummaryFile path lang mempty [TOCSummaryError (T.pack e) Nothing]
where path = T.pack $ pathKeyForBlobPair blobPair
lang = languageForBlobPair blobPair

View File

@ -46,7 +46,7 @@ termGraph blobs = distributeFoldMap go (fmap apiBlobToBlob blobs)
go :: ParseEffects sig m => Blob -> m ParseTreeGraphResponse go :: ParseEffects sig m => Blob -> m ParseTreeGraphResponse
go blob = (doParse blob >>= withSomeTerm (pure . render)) go blob = (doParse blob >>= withSomeTerm (pure . render))
`catchError` \(SomeException e) -> `catchError` \(SomeException e) ->
pure (ParseTreeGraphResponse mempty mempty [TermError (blobPath blob) (show e)]) pure (ParseTreeGraphResponse mempty mempty [ParseError (blobPath blob) (show e)])
render t = let graph = renderTreeGraph t render t = let graph = renderTreeGraph t
toEdge (Edge (a, b)) = TermEdge (vertexId a) (vertexId b) toEdge (Edge (a, b)) = TermEdge (vertexId a) (vertexId b)

View File

@ -35,7 +35,7 @@ module Semantic.API.Types
, ParseTreeGraphResponse(..) , ParseTreeGraphResponse(..)
, TermVertex(..) , TermVertex(..)
, TermEdge(..) , TermEdge(..)
, TermError(..) , ParseError(..)
-- Health Check -- Health Check
, PingRequest(..) , PingRequest(..)
@ -139,8 +139,8 @@ data Symbol
data ParseTreeGraphResponse data ParseTreeGraphResponse
= ParseTreeGraphResponse = ParseTreeGraphResponse
{ vertices :: [TermVertex] { vertices :: [TermVertex]
, edges :: [TermEdge] , edges :: [TermEdge]
, errors :: [TermError] , errors :: [ParseError]
} }
deriving stock (Eq, Show, Generic) deriving stock (Eq, Show, Generic)
deriving anyclass (Message, Named, ToJSON) deriving anyclass (Message, Named, ToJSON)
@ -156,7 +156,11 @@ data TermVertex = TermVertex { vertexId :: Int, term :: String, span :: Maybe Sp
deriving anyclass (Message, Named, ToJSON) deriving anyclass (Message, Named, ToJSON)
instance VertexTag TermVertex where uniqueTag = vertexId instance VertexTag TermVertex where uniqueTag = vertexId
data TermError = TermError { path :: String, error :: String } data ParseError
= ParseError
{ path :: String
, error :: String
}
deriving stock (Eq, Ord, Show, Generic) deriving stock (Eq, Ord, Show, Generic)
deriving anyclass (Message, Named, ToJSON) deriving anyclass (Message, Named, ToJSON)
@ -226,7 +230,11 @@ data TOCSummaryError = TOCSummaryError
-- --
data DiffTreeGraphResponse data DiffTreeGraphResponse
= DiffTreeGraphResponse { vertices :: [DiffTreeVertex], edges :: [DiffTreeEdge] } = DiffTreeGraphResponse
{ vertices :: [DiffTreeVertex]
, edges :: [DiffTreeEdge]
, errors :: [ParseError]
}
deriving stock (Eq, Show, Generic) deriving stock (Eq, Show, Generic)
deriving anyclass (Message, Named, ToJSON) deriving anyclass (Message, Named, ToJSON)
deriving Semigroup via GenericSemigroup DiffTreeGraphResponse deriving Semigroup via GenericSemigroup DiffTreeGraphResponse
@ -236,7 +244,7 @@ data DiffTreeEdge = DiffTreeEdge { source :: Int, target :: Int }
deriving stock (Eq, Ord, Show, Generic) deriving stock (Eq, Ord, Show, Generic)
deriving anyclass (Message, Named, ToJSON) deriving anyclass (Message, Named, ToJSON)
data DiffTreeVertex = DiffTreeVertex { diffVertexId :: Int, term :: Maybe DiffTreeTerm } data DiffTreeVertex = DiffTreeVertex { diffVertexId :: Int, diffTerm :: Maybe DiffTreeTerm }
deriving stock (Eq, Ord, Show, Generic) deriving stock (Eq, Ord, Show, Generic)
deriving anyclass (Message, Named, ToJSON) deriving anyclass (Message, Named, ToJSON)
instance VertexTag DiffTreeVertex where uniqueTag = diffVertexId instance VertexTag DiffTreeVertex where uniqueTag = diffVertexId