diff --git a/.hlint.yaml b/.hlint.yaml index bc1b09a86..96ea24647 100644 --- a/.hlint.yaml +++ b/.hlint.yaml @@ -48,6 +48,7 @@ - ignore: {name: Use ., within: [Analysis.Abstract.Graph.graphingModules]} - ignore: {name: Reduce duplication, within: [Semantic.Util]} +- ignore: {name: Use newtype instead of data, within: [Semantic.Api.V1.CodeAnalysisPB]} # Our customized warnings diff --git a/proto/semantic.proto b/proto/semantic/api/v1/code_analysis.proto similarity index 82% rename from proto/semantic.proto rename to proto/semantic/api/v1/code_analysis.proto index 35954303d..f4aa85167 100644 --- a/proto/semantic.proto +++ b/proto/semantic/api/v1/code_analysis.proto @@ -1,13 +1,11 @@ -// This file was generated by proto-gen. Do not edit by hand. syntax = "proto3"; -package github.semantic; +package semantic.api.v1; -option java_package = "com.github.semantic.analysis"; -option go_package = "github.com/semantic/analysis/;analysis"; - -// Semantic's CodeAnalysis service provides endpoints for parsing, analyzing, and comparing source code. +option java_package = "com.github.semantic.api.v1"; +// Semantic's CodeAnalysis service provides endpoints for parsing, analyzing, +// and comparing source code. service CodeAnalysis { // Check health & status of the service. rpc Ping (PingRequest) returns (PingResponse); @@ -58,7 +56,7 @@ message TermEdge { } message TermVertex { - int64 vertexId = 1; + int64 vertex_id = 1; string term = 2; Span span = 3; } @@ -86,7 +84,7 @@ message TOCSummaryChange { string category = 1; string term = 2; Span span = 3; - ChangeType changeType = 4; + ChangeType change_type = 4; } message TOCSummaryError { @@ -119,16 +117,12 @@ message DiffTreeEdge { } message DiffTreeVertex { - int64 diffVertexId = 1; - DiffTreeTerm diffTerm = 2; -} - -message DiffTreeTerm { - oneof sum { - DeletedTerm deleted = 1; - InsertedTerm inserted = 2; - ReplacedTerm replaced = 3; - MergedTerm merged = 4; + int64 diff_vertex_id = 1; + oneof diff_term { + DeletedTerm deleted = 2; + InsertedTerm inserted = 3; + ReplacedTerm replaced = 4; + MergedTerm merged = 5; } } @@ -143,16 +137,16 @@ message InsertedTerm { } message ReplacedTerm { - string beforeTerm = 1; - Span beforeSpan = 2; - string afterTerm = 3; - Span afterSpan = 4; + string before_term = 1; + Span before_span = 2; + string after_term = 3; + Span after_span = 4; } message MergedTerm { string term = 1; - Span beforeSpan = 2; - Span afterSpan = 3; + Span before_span = 2; + Span after_span = 3; } enum Language { diff --git a/semantic.cabal b/semantic.cabal index a2c767071..9e794ab21 100644 --- a/semantic.cabal +++ b/semantic.cabal @@ -183,14 +183,14 @@ library -- High-level flow & operational functionality (logging, stats, etc.) , Semantic.Analysis -- API - , Semantic.API - , Semantic.API.Diffs - , Semantic.API.Helpers - , Semantic.API.LegacyTypes - , Semantic.API.Symbols - , Semantic.API.Terms - , Semantic.API.TOCSummaries - , Semantic.API.Types + , Semantic.Api + , Semantic.Api.Diffs + , Semantic.Api.Helpers + , Semantic.Api.LegacyTypes + , Semantic.Api.Symbols + , Semantic.Api.Terms + , Semantic.Api.TOCSummaries + , Semantic.Api.V1.CodeAnalysisPB , Semantic.AST , Semantic.CLI , Semantic.Config diff --git a/src/Data/Graph.hs b/src/Data/Graph.hs index e036a2955..52820b4ea 100644 --- a/src/Data/Graph.hs +++ b/src/Data/Graph.hs @@ -24,6 +24,7 @@ import Control.Effect import Control.Effect.State import Data.Aeson import qualified Data.Set as Set +import Semantic.Api.V1.CodeAnalysisPB -- | An algebraic graph with 'Ord', 'Semigroup', and 'Monoid' instances. newtype Graph vertex = Graph { unGraph :: G.Graph vertex } @@ -100,6 +101,9 @@ instance Ord vertex => Ord (Graph vertex) where class VertexTag vertex where uniqueTag :: vertex -> Int +instance VertexTag DiffTreeVertex where uniqueTag = fromIntegral . diffVertexId +instance VertexTag TermVertex where uniqueTag = fromIntegral . vertexId + instance (Ord vertex, ToJSON vertex, VertexTag vertex) => ToJSON (Graph vertex) where toJSON (Graph graph) = object ["vertices" .= G.vertexList graph, "edges" .= (Edge <$> G.edgeList graph)] toEncoding (Graph graph) = pairs ("vertices" .= G.vertexList graph <> "edges" .= (Edge <$> G.edgeList graph)) diff --git a/src/Rendering/Graph.hs b/src/Rendering/Graph.hs index 3096fd6ab..f30a72db5 100644 --- a/src/Rendering/Graph.hs +++ b/src/Rendering/Graph.hs @@ -18,8 +18,10 @@ import Data.Patch import Data.String (IsString (..)) import Data.Term import Prologue -import Semantic.API.Helpers -import Semantic.API.Types +import Semantic.Api.Helpers +import Semantic.Api.V1.CodeAnalysisPB + +import qualified Data.Text as T -- TODO: rename as this isn't a render renderTreeGraph :: (Ord vertex, Recursive t, ToTreeGraph vertex (Base t)) => t -> Graph vertex @@ -45,10 +47,10 @@ diffStyle name = (defaultStyle (fromString . show . diffVertexId)) { graphName = fromString (quote name) , vertexAttributes = vertexAttributes } where quote a = "\"" <> a <> "\"" - vertexAttributes (DiffTreeVertex _ (Just (Deleted (Just DeletedTerm{..})))) = [ "label" := fromString term, "color" := "red" ] - vertexAttributes (DiffTreeVertex _ (Just (Inserted (Just InsertedTerm{..})))) = [ "label" := fromString term, "color" := "green" ] + vertexAttributes (DiffTreeVertex _ (Just (Deleted (Just DeletedTerm{..})))) = [ "label" := fromString (T.unpack term), "color" := "red" ] + vertexAttributes (DiffTreeVertex _ (Just (Inserted (Just InsertedTerm{..})))) = [ "label" := fromString (T.unpack term), "color" := "green" ] vertexAttributes (DiffTreeVertex _ (Just (Replaced (Just ReplacedTerm{..})))) = [ "label" := "Replacement", "color" := "orange", "style" := "dashed" ] - vertexAttributes (DiffTreeVertex _ (Just (Merged (Just MergedTerm{..})))) = [ "label" := fromString term ] + vertexAttributes (DiffTreeVertex _ (Just (Merged (Just MergedTerm{..})))) = [ "label" := fromString (T.unpack term) ] vertexAttributes _ = [] class ToTreeGraph vertex t | t -> vertex where @@ -70,22 +72,22 @@ instance (ConstructorName syntax, Foldable syntax) => termAlgebra (In ann syntax) = do i <- fresh parent <- ask - let root = vertex (TermVertex i (constructorName syntax) (spanToSpan (locationSpan ann))) + let root = vertex (TermVertex (fromIntegral i) (T.pack (constructorName syntax)) (spanToSpan (locationSpan ann))) subGraph <- foldl' (\acc x -> overlay <$> acc <*> local (const root) x) (pure mempty) syntax pure (parent `connect` root `overlay` subGraph) instance (ConstructorName syntax, Foldable syntax) => ToTreeGraph DiffTreeVertex (DiffF syntax Location Location) where toTreeGraph d = case d of - Merge t@(In (a1, a2) syntax) -> diffAlgebra t (Merged (Just (MergedTerm (constructorName syntax) (ann a1) (ann a2)))) - Patch (Delete t1@(In a1 syntax)) -> diffAlgebra t1 (Deleted (Just (DeletedTerm (constructorName syntax) (ann a1)))) - Patch (Insert t2@(In a2 syntax)) -> diffAlgebra t2 (Inserted (Just (InsertedTerm (constructorName syntax) (ann a2)))) + Merge t@(In (a1, a2) syntax) -> diffAlgebra t (Merged (Just (MergedTerm (T.pack (constructorName syntax)) (ann a1) (ann a2)))) + Patch (Delete t1@(In a1 syntax)) -> diffAlgebra t1 (Deleted (Just (DeletedTerm (T.pack (constructorName syntax)) (ann a1)))) + Patch (Insert t2@(In a2 syntax)) -> diffAlgebra t2 (Inserted (Just (InsertedTerm (T.pack (constructorName syntax)) (ann a2)))) Patch (Replace t1@(In a1 syntax1) t2@(In a2 syntax2)) -> do i <- fresh parent <- ask - let (beforeName, beforeSpan) = (constructorName syntax1, ann a1) - let (afterName, afterSpan) = (constructorName syntax2, ann a2) - let replace = vertex (DiffTreeVertex i (Just (Replaced (Just (ReplacedTerm beforeName beforeSpan afterName afterSpan))))) + let (beforeName, beforeSpan) = (T.pack (constructorName syntax1), ann a1) + let (afterName, afterSpan) = (T.pack (constructorName syntax2), ann a2) + let replace = vertex (DiffTreeVertex (fromIntegral i) (Just (Replaced (Just (ReplacedTerm beforeName beforeSpan afterName afterSpan))))) graph <- local (const replace) (overlay <$> diffAlgebra t1 (Deleted (Just (DeletedTerm beforeName beforeSpan))) <*> diffAlgebra t2 (Inserted (Just (InsertedTerm afterName afterSpan)))) pure (parent `connect` replace `overlay` graph) where @@ -96,10 +98,10 @@ instance (ConstructorName syntax, Foldable syntax) => , Member (Reader (Graph DiffTreeVertex)) sig , Carrier sig m , Monad m - ) => f (m (Graph DiffTreeVertex)) -> DiffTreeTerm -> m (Graph DiffTreeVertex) + ) => f (m (Graph DiffTreeVertex)) -> DiffTreeVertexDiffTerm -> m (Graph DiffTreeVertex) diffAlgebra syntax a = do i <- fresh parent <- ask - let root = vertex (DiffTreeVertex i (Just a)) + let root = vertex (DiffTreeVertex (fromIntegral i) (Just a)) subGraph <- foldl' (\acc x -> overlay <$> acc <*> local (const root) x) (pure mempty) syntax pure (parent `connect` root `overlay` subGraph) diff --git a/src/Semantic/API.hs b/src/Semantic/API.hs deleted file mode 100644 index f2659d3db..000000000 --- a/src/Semantic/API.hs +++ /dev/null @@ -1,14 +0,0 @@ -module Semantic.API - ( - module DiffsAPI - , module SymbolsAPI - , module TermsAPI - , module TOCSummariesAPI - , module Types - ) where - -import Semantic.API.Diffs as DiffsAPI -import Semantic.API.Symbols as SymbolsAPI -import Semantic.API.Terms as TermsAPI -import Semantic.API.TOCSummaries as TOCSummariesAPI -import Semantic.API.Types as Types diff --git a/src/Semantic/API/Types.hs b/src/Semantic/API/Types.hs deleted file mode 100644 index 06b72e2bd..000000000 --- a/src/Semantic/API/Types.hs +++ /dev/null @@ -1,343 +0,0 @@ -{-# LANGUAGE DerivingVia, DeriveAnyClass, DuplicateRecordFields, LambdaCase #-} -module Semantic.API.Types - ( - -- Parse APIs - ParseTreeRequest(..) - , Blob(..) - , BlobPair(..) - - -- Symbols for jump-to-definition - , ParseTreeSymbolResponse(..) - , File(..) - , Symbol(..) - - -- Diff APIs - , DiffTreeRequest(..) - - -- TOC Summaries - , DiffTreeTOCResponse(..) - , TOCSummaryFile(..) - , TOCSummaryChange(..) - , TOCSummaryError(..) - , ChangeType(..) - - -- Diff tree graphs - , DiffTreeGraphResponse(..) - , DiffTreeFileGraph(..) - , DiffTreeEdge(..) - , DiffTreeVertex(..) - , DiffTreeTerm(..) - , DeletedTerm(..) - , InsertedTerm(..) - , ReplacedTerm(..) - , MergedTerm(..) - - -- Parse tree graphs - , ParseTreeGraphResponse(..) - , ParseTreeFileGraph(..) - , TermVertex(..) - , TermEdge(..) - , ParseError(..) - - -- Health Check - , PingRequest(..) - , PingResponse(..) - - -- Common Types - , Span(..) - , Position(..) - - -- Mime Types - , Protobuf - ) where - -import Data.Aeson -import Data.Bifunctor (first) -import Data.ByteString.Lazy.Char8 as BC -import Data.Char (toUpper) -import Data.Graph (VertexTag (..)) -import Data.Language -import Data.String -import qualified Data.Text as T -import GHC.Generics -import Network.HTTP.Media ((//)) -import Prologue -import Proto3.Suite as Proto3 -import Servant.API - --- These types represent the public API of semantic and are used to generate --- `proto/semantic.proto`. --- --- Some guidelines: --- --- * Don't write Message, Named, ToJSON, or FromJSON instances by hand, derive --- them. --- --- * For non-primitive types, you'll always want to use Maybe as protobuf --- fields are always optional. --- --- * It's usually best to map internal types to these API types so that the --- API contract can be changed intentionally. This also makes it so that core --- functionality doesn't have to deal with all the Maybes. --- --- * Keep field names short and meaningful for external consumers. It's better --- to skirt Haskell naming conventions in favor of consistency in our proto --- files. - --- --- Parse/Term APIs --- - -newtype ParseTreeRequest = ParseTreeRequest { blobs :: [Blob] } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, FromJSON) - -data Blob - = Blob - { content :: T.Text - , path :: FilePath - , language :: Language - } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, FromJSON) - -data BlobPair - = BlobPair - { before :: Maybe Blob - , after :: Maybe Blob - } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, FromJSON) - --- --- Symbols API --- -newtype ParseTreeSymbolResponse = ParseTreeSymbolResponse { files :: [File] } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data File - = File - { path :: T.Text - , language :: Language - , symbols :: [Symbol] - , errors :: [ParseError] - } - deriving stock (Generic, Eq, Show) - deriving anyclass (Named, Message, ToJSON) - -data Symbol - = Symbol - { symbol :: T.Text - , kind :: T.Text - , line :: T.Text - , span :: Maybe Span - } - deriving stock (Generic, Eq, Show) - deriving anyclass (Named, Message, ToJSON) - --- --- Term Graph API --- -newtype ParseTreeGraphResponse = ParseTreeGraphResponse { files :: [ParseTreeFileGraph] } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data ParseTreeFileGraph - = ParseTreeFileGraph - { path :: T.Text - , language :: Language - , vertices :: [TermVertex] - , edges :: [TermEdge] - , errors :: [ParseError] - } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data TermEdge = TermEdge { source :: Int, target :: Int } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data TermVertex = TermVertex { vertexId :: Int, term :: String, span :: Maybe Span } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) -instance VertexTag TermVertex where uniqueTag = vertexId - -newtype ParseError = ParseError { error :: String } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - --- --- Diff APIs --- - -newtype DiffTreeRequest = DiffTreeRequest { blobs :: [BlobPair] } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, FromJSON) - --- --- TOC Summaries API --- -newtype DiffTreeTOCResponse = DiffTreeTOCResponse { files :: [TOCSummaryFile] } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data TOCSummaryFile = TOCSummaryFile - { path :: T.Text - , language :: Language - , changes :: [TOCSummaryChange] - , errors :: [TOCSummaryError] - } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data TOCSummaryChange = TOCSummaryChange - { category :: T.Text - , term :: T.Text - , span :: Maybe Span - , changeType :: ChangeType - } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data ChangeType - = None - | Added - | Removed - | Modified - deriving stock (Eq, Ord, Show, Enum, Bounded, Generic) - deriving anyclass (Named, MessageField, ToJSON) - -instance HasDefault ChangeType where def = None - -instance Finite ChangeType where - enumerate _ = fmap go [None ..] where - go x = (fromString (fmap toUpper (show x)), fromEnum x) - -instance Primitive ChangeType where - primType _ = primType (Proxy @(Enumerated ChangeType)) - encodePrimitive f = encodePrimitive f . Enumerated . Right - decodePrimitive = decodePrimitive >>= \case - (Enumerated (Right r)) -> pure r - other -> Prelude.fail ("ChangeType decodeMessageField: unexpected value" <> show other) - -data TOCSummaryError = TOCSummaryError - { error :: T.Text - , span :: Maybe Span - } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - --- --- Diff Tree Graph API --- - -newtype DiffTreeGraphResponse = DiffTreeGraphResponse { files :: [DiffTreeFileGraph] } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data DiffTreeFileGraph - = DiffTreeFileGraph - { path :: T.Text - , language :: Language - , vertices :: [DiffTreeVertex] - , edges :: [DiffTreeEdge] - , errors :: [ParseError] - } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data DiffTreeEdge = DiffTreeEdge { source :: Int, target :: Int } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data DiffTreeVertex = DiffTreeVertex { diffVertexId :: Int, diffTerm :: Maybe DiffTreeTerm } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) -instance VertexTag DiffTreeVertex where uniqueTag = diffVertexId - --- NB: Current proto generation only supports sum types with single named fields. -data DiffTreeTerm - = Deleted { deleted :: Maybe DeletedTerm } - | Inserted { inserted :: Maybe InsertedTerm } - | Replaced { replaced :: Maybe ReplacedTerm } - | Merged { merged :: Maybe MergedTerm } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data DeletedTerm = DeletedTerm { term :: String, span :: Maybe Span } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data InsertedTerm = InsertedTerm { term :: String, span :: Maybe Span } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data ReplacedTerm = ReplacedTerm { beforeTerm :: String, beforeSpan :: Maybe Span, afterTerm :: String, afterSpan :: Maybe Span } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data MergedTerm = MergedTerm { term :: String, beforeSpan :: Maybe Span, afterSpan :: Maybe Span } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - - --- --- Health Check API --- - -newtype PingRequest = PingRequest { service :: String } - deriving stock (Eq, Show, Generic) - deriving anyclass (Message, Named, FromJSON) - -data PingResponse - = PingResponse - { status :: String - , hostname :: String - , timestamp :: String - , sha :: String - } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -instance MimeRender PlainText PingResponse where - mimeRender _ PingResponse{..} = BC.pack $ - status <> " - " <> hostname <> " - " <> sha <> " - " <> timestamp <> "\n" - - --- --- Common Types --- - -data Position = Position - { line :: Int - , column :: Int - } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - -data Span = Span - { start :: Maybe Position - , end :: Maybe Position - } - deriving stock (Eq, Ord, Show, Generic) - deriving anyclass (Message, Named, ToJSON) - --- --- Custom Mime Types --- --- Servant doesn't come with protobuf support out of the box, but it's --- very easy to add this as a valid type for decoding and encoding: all --- you have to do is map proto3-suite's encoding and decoding functions --- to the MimeRender/MimeUnrender typeclasses. - -data Protobuf - -instance Accept Protobuf where - contentType _ = "application" // "protobuf" - -instance Message a => MimeRender Protobuf a where - mimeRender _ = Proto3.toLazyByteString - -instance Message a => MimeUnrender Protobuf a where - mimeUnrender _ = first show . Proto3.fromByteString . BC.toStrict diff --git a/src/Semantic/Api.hs b/src/Semantic/Api.hs new file mode 100644 index 000000000..a284654af --- /dev/null +++ b/src/Semantic/Api.hs @@ -0,0 +1,14 @@ +module Semantic.Api + ( + module DiffsAPI + , module SymbolsAPI + , module TermsAPI + , module TOCSummariesAPI + , module Types + ) where + +import Semantic.Api.Diffs as DiffsAPI +import Semantic.Api.Symbols as SymbolsAPI +import Semantic.Api.Terms as TermsAPI +import Semantic.Api.TOCSummaries as TOCSummariesAPI +import Semantic.Api.V1.CodeAnalysisPB as Types hiding (Language(..)) diff --git a/src/Semantic/API/Diffs.hs b/src/Semantic/Api/Diffs.hs similarity index 91% rename from src/Semantic/API/Diffs.hs rename to src/Semantic/Api/Diffs.hs index f3f61c41e..4ff363278 100644 --- a/src/Semantic/API/Diffs.hs +++ b/src/Semantic/Api/Diffs.hs @@ -1,5 +1,5 @@ {-# LANGUAGE GADTs, ConstraintKinds, TypeOperators, RankNTypes #-} -module Semantic.API.Diffs +module Semantic.Api.Diffs ( parseDiffBuilder , DiffOutputFormat(..) , diffGraph @@ -26,15 +26,16 @@ import Data.Language import Data.Location import Data.Term import qualified Data.Text as T +import qualified Data.Vector as V import Diffing.Algorithm (Diffable) import Parsing.Parser import Prologue import Rendering.Graph import Rendering.JSON hiding (JSON) import qualified Rendering.JSON -import Semantic.API.Helpers -import Semantic.API.Types hiding (Blob, BlobPair) -import qualified Semantic.API.Types as API +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) @@ -72,21 +73,21 @@ renderJSONGraph :: (Applicative m, Functor syntax, Foldable syntax, ConstructorN renderJSONGraph blobPair = pure . renderJSONAdjDiff blobPair . renderTreeGraph diffGraph :: (Traversable t, DiffEffects sig m) => t API.BlobPair -> m DiffTreeGraphResponse -diffGraph blobs = DiffTreeGraphResponse . toList <$> distributeFor (apiBlobPairToBlobPair <$> blobs) go +diffGraph blobs = DiffTreeGraphResponse . V.fromList . toList <$> distributeFor (apiBlobPairToBlobPair <$> blobs) go where go :: (DiffEffects sig m) => BlobPair -> m DiffTreeFileGraph go blobPair = doDiff blobPair (const pure) render `catchError` \(SomeException e) -> - pure (DiffTreeFileGraph path lang mempty mempty [ParseError (show e)]) + pure (DiffTreeFileGraph path lang mempty mempty (V.fromList [ParseError (T.pack (show e))])) where path = T.pack $ pathForBlobPair blobPair - lang = languageForBlobPair blobPair + lang = languageToApiLanguage $ languageForBlobPair blobPair render :: (Foldable syntax, Functor syntax, ConstructorName syntax, Applicative m) => BlobPair -> Diff syntax Location Location -> m DiffTreeFileGraph render _ diff = let graph = renderTreeGraph diff toEdge (Edge (a, b)) = DiffTreeEdge (diffVertexId a) (diffVertexId b) - in pure $ DiffTreeFileGraph path lang (vertexList graph) (fmap toEdge (edgeList graph)) mempty + in pure $ DiffTreeFileGraph path lang (V.fromList (vertexList graph)) (V.fromList (fmap toEdge (edgeList graph))) mempty sexpDiff :: (DiffEffects sig m) => BlobPair -> m Builder diff --git a/src/Semantic/API/Helpers.hs b/src/Semantic/Api/Helpers.hs similarity index 51% rename from src/Semantic/API/Helpers.hs rename to src/Semantic/Api/Helpers.hs index a942fe365..5e86bc458 100644 --- a/src/Semantic/API/Helpers.hs +++ b/src/Semantic/Api/Helpers.hs @@ -1,24 +1,27 @@ {-# LANGUAGE LambdaCase #-} -module Semantic.API.Helpers +module Semantic.Api.Helpers ( spanToSpan , spanToLegacySpan , toChangeType , apiBlobToBlob , apiBlobPairToBlobPair + , apiLanguageToLanguage + , languageToApiLanguage ) where import Data.Bifunctor.Join import qualified Data.Blob as Data +import qualified Data.Language as Data import Data.Source (fromText) import qualified Data.Span as Data import qualified Data.Text as T import Data.These -import qualified Semantic.API.LegacyTypes as Legacy -import qualified Semantic.API.Types as API +import qualified Semantic.Api.LegacyTypes as Legacy +import qualified Semantic.Api.V1.CodeAnalysisPB as API spanToSpan :: Data.Span -> Maybe API.Span spanToSpan Data.Span{..} = Just $ API.Span (toPos spanStart) (toPos spanEnd) - where toPos Data.Pos{..} = Just $ API.Position posLine posColumn + where toPos Data.Pos{..} = Just $ API.Position (fromIntegral posLine) (fromIntegral posColumn) spanToLegacySpan :: Data.Span -> Maybe Legacy.Span spanToLegacySpan Data.Span{..} = Just $ Legacy.Span (toPos spanStart) (toPos spanEnd) @@ -32,7 +35,37 @@ toChangeType = \case _ -> API.None apiBlobToBlob :: API.Blob -> Data.Blob -apiBlobToBlob API.Blob{..} = Data.Blob (fromText content) path language +apiBlobToBlob API.Blob{..} = Data.Blob (fromText content) (T.unpack path) (apiLanguageToLanguage language) + +apiLanguageToLanguage :: API.Language -> Data.Language +apiLanguageToLanguage = \case + API.Unknown -> Data.Unknown + API.Go -> Data.Go + API.Haskell -> Data.Haskell + API.Java -> Data.Java + API.Javascript -> Data.JavaScript + API.Json -> Data.JSON + API.Jsx -> Data.JSX + API.Markdown -> Data.Markdown + API.Python -> Data.Python + API.Ruby -> Data.Ruby + 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 apiBlobPairToBlobPair :: API.BlobPair -> Data.BlobPair apiBlobPairToBlobPair (API.BlobPair (Just before) (Just after)) = Join (These (apiBlobToBlob before) (apiBlobToBlob after)) diff --git a/src/Semantic/API/LegacyTypes.hs b/src/Semantic/Api/LegacyTypes.hs similarity index 98% rename from src/Semantic/API/LegacyTypes.hs rename to src/Semantic/Api/LegacyTypes.hs index 2bde52f7d..5aebf7cb0 100644 --- a/src/Semantic/API/LegacyTypes.hs +++ b/src/Semantic/Api/LegacyTypes.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DerivingVia, DeriveAnyClass, DuplicateRecordFields #-} -module Semantic.API.LegacyTypes +module Semantic.Api.LegacyTypes ( DiffTreeRequest(..) , ParseTreeRequest(..) , ParseTreeSymbolResponse(..) diff --git a/src/Semantic/API/Symbols.hs b/src/Semantic/Api/Symbols.hs similarity index 79% rename from src/Semantic/API/Symbols.hs rename to src/Semantic/Api/Symbols.hs index cf1fad8c8..aba033100 100644 --- a/src/Semantic/API/Symbols.hs +++ b/src/Semantic/Api/Symbols.hs @@ -1,5 +1,5 @@ {-# LANGUAGE GADTs, TypeOperators, DerivingStrategies #-} -module Semantic.API.Symbols +module Semantic.Api.Symbols ( legacyParseSymbols , parseSymbols , parseSymbolsBuilder @@ -13,14 +13,16 @@ import Data.ByteString.Builder import Data.Location import Data.Maybe import Data.Term +import qualified Data.Text as T +import qualified Data.Vector as V import Data.Text (pack) import Parsing.Parser import Prologue -import Semantic.API.Helpers -import qualified Semantic.API.LegacyTypes as Legacy -import Semantic.API.Terms (ParseEffects, doParse) -import Semantic.API.Types hiding (Blob) -import qualified Semantic.API.Types as API +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 @@ -54,18 +56,18 @@ parseSymbolsBuilder blobs = legacyParseSymbols blobs >>= serialize JSON parseSymbols :: (Member Distribute sig, ParseEffects sig m, Traversable t) => t API.Blob -> m ParseTreeSymbolResponse -parseSymbols blobs = ParseTreeSymbolResponse . toList <$> distributeFor (apiBlobToBlob <$> blobs) go +parseSymbols blobs = ParseTreeSymbolResponse . V.fromList . toList <$> distributeFor (apiBlobToBlob <$> 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)) where - errorFile e = File (pack blobPath) blobLanguage mempty [ParseError e] + errorFile e = File (pack blobPath) (languageToApiLanguage blobLanguage) mempty (V.fromList [ParseError (T.pack e)]) renderToSymbols :: (IsTaggable f, Applicative m) => Blob -> Term f Location -> m File renderToSymbols blob@Blob{..} term = pure $ either (errorFile . show) (tagsToFile blob) (runTagging blob term) tagsToFile :: Blob -> [Tag] -> File - tagsToFile Blob{..} tags = File (pack blobPath) blobLanguage (fmap tagToSymbol tags) mempty + tagsToFile Blob{..} tags = File (pack blobPath) (languageToApiLanguage blobLanguage) (V.fromList (fmap tagToSymbol tags)) mempty tagToSymbol :: Tag -> Symbol tagToSymbol Tag{..} diff --git a/src/Semantic/API/TOCSummaries.hs b/src/Semantic/Api/TOCSummaries.hs similarity index 70% rename from src/Semantic/API/TOCSummaries.hs rename to src/Semantic/Api/TOCSummaries.hs index 580807bfa..ff8d7c0b7 100644 --- a/src/Semantic/API/TOCSummaries.hs +++ b/src/Semantic/Api/TOCSummaries.hs @@ -1,5 +1,5 @@ {-# LANGUAGE GADTs, TypeOperators, DerivingStrategies #-} -module Semantic.API.TOCSummaries (diffSummary, legacyDiffSummary, diffSummaryBuilder) where +module Semantic.Api.TOCSummaries (diffSummary, legacyDiffSummary, diffSummaryBuilder) where import Analysis.TOCSummary (Declaration, declarationAlgebra) import Control.Effect.Error @@ -10,11 +10,12 @@ import Data.Diff import qualified Data.Map.Monoidal as Map import Data.Span (emptySpan) import qualified Data.Text as T +import qualified Data.Vector as V import Rendering.TOC -import Semantic.API.Diffs -import Semantic.API.Helpers -import Semantic.API.Types hiding (Blob, BlobPair) -import qualified Semantic.API.Types as API +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 @@ -37,23 +38,23 @@ legacyDiffSummary = distributeFoldMap go render blobPair = pure . renderToCDiff blobPair diffSummary :: (DiffEffects sig m) => [API.BlobPair] -> m DiffTreeTOCResponse -diffSummary blobs = DiffTreeTOCResponse <$> distributeFor (apiBlobPairToBlobPair <$> blobs) go +diffSummary blobs = DiffTreeTOCResponse . V.fromList <$> distributeFor (apiBlobPairToBlobPair <$> blobs) go where go :: (DiffEffects sig m) => BlobPair -> m TOCSummaryFile go blobPair = doDiff blobPair (decorate . declarationAlgebra) render `catchError` \(SomeException e) -> - pure $ TOCSummaryFile path lang mempty [TOCSummaryError (T.pack (show e)) Nothing] + pure $ TOCSummaryFile path lang mempty (V.fromList [TOCSummaryError (T.pack (show e)) Nothing]) where path = T.pack $ pathKeyForBlobPair blobPair - lang = languageForBlobPair blobPair + lang = languageToApiLanguage $ languageForBlobPair blobPair 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) where path = T.pack $ pathKeyForBlobPair blobPair - lang = languageForBlobPair blobPair + lang = languageToApiLanguage $ languageForBlobPair blobPair go :: TOCSummary -> TOCSummaryFile -> TOCSummaryFile go TOCSummary{..} TOCSummaryFile{..} - = TOCSummaryFile path language (TOCSummaryChange summaryCategoryName summaryTermName (spanToSpan summarySpan) (toChangeType summaryChangeType) : changes) errors + = TOCSummaryFile path language (V.cons (TOCSummaryChange summaryCategoryName summaryTermName (spanToSpan summarySpan) (toChangeType summaryChangeType)) changes) errors go ErrorSummary{..} TOCSummaryFile{..} - = TOCSummaryFile path language changes (TOCSummaryError errorText (spanToSpan errorSpan) : errors) + = TOCSummaryFile path language changes (V.cons (TOCSummaryError errorText (spanToSpan errorSpan)) errors) diff --git a/src/Semantic/API/Terms.hs b/src/Semantic/Api/Terms.hs similarity index 87% rename from src/Semantic/API/Terms.hs rename to src/Semantic/Api/Terms.hs index f920d086a..c2d58a4ad 100644 --- a/src/Semantic/API/Terms.hs +++ b/src/Semantic/Api/Terms.hs @@ -1,5 +1,5 @@ {-# LANGUAGE ConstraintKinds, GADTs, TypeOperators, DerivingStrategies #-} -module Semantic.API.Terms +module Semantic.Api.Terms ( termGraph , parseTermBuilder @@ -28,36 +28,37 @@ import Data.JSON.Fields import Data.Language import Data.Location import Data.Quieterm +import Data.Term import qualified Data.Text as T +import qualified Data.Vector as V import Parsing.Parser import Prologue import Rendering.Graph import Rendering.JSON hiding (JSON) import qualified Rendering.JSON -import Semantic.API.Helpers -import Semantic.API.Types hiding (Blob) -import qualified Semantic.API.Types as API +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 -import Data.Term termGraph :: (Traversable t, Member Distribute sig, ParseEffects sig m) => t API.Blob -> m ParseTreeGraphResponse -termGraph blobs = ParseTreeGraphResponse . toList <$> distributeFor (fmap apiBlobToBlob blobs) go +termGraph blobs = ParseTreeGraphResponse . V.fromList . toList <$> distributeFor (fmap apiBlobToBlob blobs) go where go :: ParseEffects sig m => Blob -> m ParseTreeFileGraph go blob = (doParse blob >>= withSomeTerm (pure . render)) `catchError` \(SomeException e) -> - pure (ParseTreeFileGraph path lang mempty mempty [ParseError (show e)]) + pure (ParseTreeFileGraph path lang mempty mempty (V.fromList [ParseError (T.pack (show e))])) where - path = T.pack (blobPath blob) - lang = blobLanguage blob + path = T.pack $ blobPath blob + lang = languageToApiLanguage $ blobLanguage blob render :: (Foldable syntax, Functor syntax, ConstructorName syntax) => Term syntax Location -> ParseTreeFileGraph render t = let graph = renderTreeGraph t toEdge (Edge (a, b)) = TermEdge (vertexId a) (vertexId b) - in ParseTreeFileGraph path lang (vertexList graph) (fmap toEdge (edgeList graph)) mempty + in ParseTreeFileGraph path lang (V.fromList (vertexList graph)) (V.fromList (fmap toEdge (edgeList graph))) mempty data TermOutputFormat = TermJSONTree diff --git a/src/Semantic/Api/V1/CodeAnalysisPB.hs b/src/Semantic/Api/V1/CodeAnalysisPB.hs new file mode 100644 index 000000000..08811a2e7 --- /dev/null +++ b/src/Semantic/Api/V1/CodeAnalysisPB.hs @@ -0,0 +1,548 @@ +-- Code generated by protoc-gen-haskell 0.1.0, DO NOT EDIT. +{-# LANGUAGE DerivingVia, DeriveAnyClass, DuplicateRecordFields #-} +{-# OPTIONS_GHC -Wno-unused-imports -Wno-missing-export-lists #-} +module Semantic.Api.V1.CodeAnalysisPB where + +import Data.Aeson +import Data.ByteString (ByteString) +import Data.Int +import Data.Text (Text) +import Data.Vector (Vector) +import Data.Word +import GHC.Generics +import Proto3.Suite +import Proto3.Wire (at, oneof) + +data PingRequest = PingRequest + { service :: Text + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message PingRequest where + encodeMessage _ PingRequest{..} = mconcat + [ encodeMessageField 1 service + ] + decodeMessage _ = PingRequest + <$> at decodeMessageField 1 + dotProto = undefined + +data PingResponse = PingResponse + { status :: Text + , hostname :: Text + , timestamp :: Text + , sha :: Text + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message PingResponse where + encodeMessage _ PingResponse{..} = mconcat + [ encodeMessageField 1 status + , encodeMessageField 2 hostname + , encodeMessageField 3 timestamp + , encodeMessageField 4 sha + ] + decodeMessage _ = PingResponse + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + <*> at decodeMessageField 3 + <*> at decodeMessageField 4 + dotProto = undefined + +data ParseTreeRequest = ParseTreeRequest + { blobs :: Vector Blob + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message ParseTreeRequest where + encodeMessage _ ParseTreeRequest{..} = mconcat + [ encodeMessageField 1 (NestedVec blobs) + ] + decodeMessage _ = ParseTreeRequest + <$> (nestedvec <$> at decodeMessageField 1) + dotProto = undefined + +data ParseTreeSymbolResponse = ParseTreeSymbolResponse + { files :: Vector File + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message ParseTreeSymbolResponse where + encodeMessage _ ParseTreeSymbolResponse{..} = mconcat + [ encodeMessageField 1 (NestedVec files) + ] + decodeMessage _ = ParseTreeSymbolResponse + <$> (nestedvec <$> at decodeMessageField 1) + dotProto = undefined + +data ParseTreeGraphResponse = ParseTreeGraphResponse + { files :: Vector ParseTreeFileGraph + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message ParseTreeGraphResponse where + encodeMessage _ ParseTreeGraphResponse{..} = mconcat + [ encodeMessageField 1 (NestedVec files) + ] + decodeMessage _ = ParseTreeGraphResponse + <$> (nestedvec <$> at decodeMessageField 1) + dotProto = undefined + +data ParseTreeFileGraph = ParseTreeFileGraph + { path :: Text + , language :: Language + , vertices :: Vector TermVertex + , edges :: Vector TermEdge + , errors :: Vector ParseError + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message ParseTreeFileGraph where + encodeMessage _ ParseTreeFileGraph{..} = mconcat + [ encodeMessageField 1 path + , encodeMessageField 2 language + , encodeMessageField 3 (NestedVec vertices) + , encodeMessageField 4 (NestedVec edges) + , encodeMessageField 5 (NestedVec errors) + ] + decodeMessage _ = ParseTreeFileGraph + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + <*> (nestedvec <$> at decodeMessageField 3) + <*> (nestedvec <$> at decodeMessageField 4) + <*> (nestedvec <$> at decodeMessageField 5) + dotProto = undefined + +data TermEdge = TermEdge + { source :: Int64 + , target :: Int64 + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message TermEdge where + encodeMessage _ TermEdge{..} = mconcat + [ encodeMessageField 1 source + , encodeMessageField 2 target + ] + decodeMessage _ = TermEdge + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + dotProto = undefined + +data TermVertex = TermVertex + { vertexId :: Int64 + , term :: Text + , span :: Maybe Span + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message TermVertex where + encodeMessage _ TermVertex{..} = mconcat + [ encodeMessageField 1 vertexId + , encodeMessageField 2 term + , encodeMessageField 3 (Nested span) + ] + decodeMessage _ = TermVertex + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + <*> at decodeMessageField 3 + dotProto = undefined + +data ParseError = ParseError + { error :: Text + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message ParseError where + encodeMessage _ ParseError{..} = mconcat + [ encodeMessageField 1 error + ] + decodeMessage _ = ParseError + <$> at decodeMessageField 1 + dotProto = undefined + +data DiffTreeRequest = DiffTreeRequest + { blobs :: Vector BlobPair + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message DiffTreeRequest where + encodeMessage _ DiffTreeRequest{..} = mconcat + [ encodeMessageField 1 (NestedVec blobs) + ] + decodeMessage _ = DiffTreeRequest + <$> (nestedvec <$> at decodeMessageField 1) + dotProto = undefined + +data DiffTreeTOCResponse = DiffTreeTOCResponse + { files :: Vector TOCSummaryFile + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message DiffTreeTOCResponse where + encodeMessage _ DiffTreeTOCResponse{..} = mconcat + [ encodeMessageField 1 (NestedVec files) + ] + decodeMessage _ = DiffTreeTOCResponse + <$> (nestedvec <$> at decodeMessageField 1) + dotProto = undefined + +data TOCSummaryFile = TOCSummaryFile + { path :: Text + , language :: Language + , changes :: Vector TOCSummaryChange + , errors :: Vector TOCSummaryError + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message TOCSummaryFile where + encodeMessage _ TOCSummaryFile{..} = mconcat + [ encodeMessageField 1 path + , encodeMessageField 2 language + , encodeMessageField 3 (NestedVec changes) + , encodeMessageField 4 (NestedVec errors) + ] + decodeMessage _ = TOCSummaryFile + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + <*> (nestedvec <$> at decodeMessageField 3) + <*> (nestedvec <$> at decodeMessageField 4) + dotProto = undefined + +data TOCSummaryChange = TOCSummaryChange + { category :: Text + , term :: Text + , span :: Maybe Span + , changeType :: ChangeType + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message TOCSummaryChange where + encodeMessage _ TOCSummaryChange{..} = mconcat + [ encodeMessageField 1 category + , encodeMessageField 2 term + , encodeMessageField 3 (Nested span) + , encodeMessageField 4 changeType + ] + decodeMessage _ = TOCSummaryChange + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + <*> at decodeMessageField 3 + <*> at decodeMessageField 4 + dotProto = undefined + +data TOCSummaryError = TOCSummaryError + { error :: Text + , span :: Maybe Span + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message TOCSummaryError where + encodeMessage _ TOCSummaryError{..} = mconcat + [ encodeMessageField 1 error + , encodeMessageField 2 (Nested span) + ] + decodeMessage _ = TOCSummaryError + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + dotProto = undefined + +data DiffTreeGraphResponse = DiffTreeGraphResponse + { files :: Vector DiffTreeFileGraph + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message DiffTreeGraphResponse where + encodeMessage _ DiffTreeGraphResponse{..} = mconcat + [ encodeMessageField 1 (NestedVec files) + ] + decodeMessage _ = DiffTreeGraphResponse + <$> (nestedvec <$> at decodeMessageField 1) + dotProto = undefined + +data DiffTreeFileGraph = DiffTreeFileGraph + { path :: Text + , language :: Language + , vertices :: Vector DiffTreeVertex + , edges :: Vector DiffTreeEdge + , errors :: Vector ParseError + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message DiffTreeFileGraph where + encodeMessage _ DiffTreeFileGraph{..} = mconcat + [ encodeMessageField 1 path + , encodeMessageField 2 language + , encodeMessageField 3 (NestedVec vertices) + , encodeMessageField 4 (NestedVec edges) + , encodeMessageField 5 (NestedVec errors) + ] + decodeMessage _ = DiffTreeFileGraph + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + <*> (nestedvec <$> at decodeMessageField 3) + <*> (nestedvec <$> at decodeMessageField 4) + <*> (nestedvec <$> at decodeMessageField 5) + dotProto = undefined + +data DiffTreeEdge = DiffTreeEdge + { source :: Int64 + , target :: Int64 + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message DiffTreeEdge where + encodeMessage _ DiffTreeEdge{..} = mconcat + [ encodeMessageField 1 source + , encodeMessageField 2 target + ] + decodeMessage _ = DiffTreeEdge + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + dotProto = undefined + +data DiffTreeVertexDiffTerm + = Deleted { deleted :: Maybe DeletedTerm } + | Inserted { inserted :: Maybe InsertedTerm } + | Replaced { replaced :: Maybe ReplacedTerm } + | Merged { merged :: Maybe MergedTerm } + deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Message, Named, FromJSON, ToJSON) + +data DiffTreeVertex = DiffTreeVertex + { diffVertexId :: Int64 + , diffTerm :: Maybe DiffTreeVertexDiffTerm + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message DiffTreeVertex where + encodeMessage _ DiffTreeVertex{..} = mconcat + [ encodeMessageField 1 diffVertexId + , case diffTerm of + Nothing -> mempty + Just (Deleted deleted) -> encodeMessageField 2 deleted + Just (Inserted inserted) -> encodeMessageField 3 inserted + Just (Replaced replaced) -> encodeMessageField 4 replaced + Just (Merged merged) -> encodeMessageField 5 merged + ] + decodeMessage _ = DiffTreeVertex + <$> at decodeMessageField 1 + <*> oneof + Nothing + [ (2, Just . Deleted <$> decodeMessageField) + , (3, Just . Inserted <$> decodeMessageField) + , (4, Just . Replaced <$> decodeMessageField) + , (5, Just . Merged <$> decodeMessageField) + ] + dotProto = undefined + +data DeletedTerm = DeletedTerm + { term :: Text + , span :: Maybe Span + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message DeletedTerm where + encodeMessage _ DeletedTerm{..} = mconcat + [ encodeMessageField 1 term + , encodeMessageField 2 (Nested span) + ] + decodeMessage _ = DeletedTerm + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + dotProto = undefined + +data InsertedTerm = InsertedTerm + { term :: Text + , span :: Maybe Span + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message InsertedTerm where + encodeMessage _ InsertedTerm{..} = mconcat + [ encodeMessageField 1 term + , encodeMessageField 2 (Nested span) + ] + decodeMessage _ = InsertedTerm + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + dotProto = undefined + +data ReplacedTerm = ReplacedTerm + { beforeTerm :: Text + , beforeSpan :: Maybe Span + , afterTerm :: Text + , afterSpan :: Maybe Span + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message ReplacedTerm where + encodeMessage _ ReplacedTerm{..} = mconcat + [ encodeMessageField 1 beforeTerm + , encodeMessageField 2 (Nested beforeSpan) + , encodeMessageField 3 afterTerm + , encodeMessageField 4 (Nested afterSpan) + ] + decodeMessage _ = ReplacedTerm + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + <*> at decodeMessageField 3 + <*> at decodeMessageField 4 + dotProto = undefined + +data MergedTerm = MergedTerm + { term :: Text + , beforeSpan :: Maybe Span + , afterSpan :: Maybe Span + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message MergedTerm where + encodeMessage _ MergedTerm{..} = mconcat + [ encodeMessageField 1 term + , encodeMessageField 2 (Nested beforeSpan) + , encodeMessageField 3 (Nested afterSpan) + ] + decodeMessage _ = MergedTerm + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + <*> at decodeMessageField 3 + dotProto = undefined + +data Blob = Blob + { content :: Text + , path :: Text + , language :: Language + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message Blob where + encodeMessage _ Blob{..} = mconcat + [ encodeMessageField 1 content + , encodeMessageField 2 path + , encodeMessageField 3 language + ] + decodeMessage _ = Blob + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + <*> at decodeMessageField 3 + dotProto = undefined + +data BlobPair = BlobPair + { before :: Maybe Blob + , after :: Maybe Blob + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message BlobPair where + encodeMessage _ BlobPair{..} = mconcat + [ encodeMessageField 1 (Nested before) + , encodeMessageField 2 (Nested after) + ] + decodeMessage _ = BlobPair + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + dotProto = undefined + +data File = File + { path :: Text + , language :: Language + , symbols :: Vector Symbol + , errors :: Vector ParseError + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message File where + encodeMessage _ File{..} = mconcat + [ encodeMessageField 1 path + , encodeMessageField 2 language + , encodeMessageField 3 (NestedVec symbols) + , encodeMessageField 4 (NestedVec errors) + ] + decodeMessage _ = File + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + <*> (nestedvec <$> at decodeMessageField 3) + <*> (nestedvec <$> at decodeMessageField 4) + dotProto = undefined + +data Symbol = Symbol + { symbol :: Text + , kind :: Text + , line :: Text + , span :: Maybe Span + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message Symbol where + encodeMessage _ Symbol{..} = mconcat + [ encodeMessageField 1 symbol + , encodeMessageField 2 kind + , encodeMessageField 3 line + , encodeMessageField 4 (Nested span) + ] + decodeMessage _ = Symbol + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + <*> at decodeMessageField 3 + <*> at decodeMessageField 4 + dotProto = undefined + +data Position = Position + { line :: Int64 + , column :: Int64 + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message Position where + encodeMessage _ Position{..} = mconcat + [ encodeMessageField 1 line + , encodeMessageField 2 column + ] + decodeMessage _ = Position + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + dotProto = undefined + +data Span = Span + { start :: Maybe Position + , end :: Maybe Position + } deriving stock (Eq, Ord, Show, Generic) + deriving anyclass (Named, FromJSON, ToJSON) + +instance Message Span where + encodeMessage _ Span{..} = mconcat + [ encodeMessageField 1 (Nested start) + , encodeMessageField 2 (Nested end) + ] + decodeMessage _ = Span + <$> at decodeMessageField 1 + <*> at decodeMessageField 2 + dotProto = undefined + +data ChangeType + = None + | Added + | Removed + | Modified + deriving stock (Eq, Ord, Show, Enum, Bounded, Generic) + deriving anyclass (Named, MessageField, FromJSON, ToJSON) + deriving Primitive via PrimitiveEnum ChangeType +instance HasDefault ChangeType where def = None + +data Language + = Unknown + | Go + | Haskell + | Java + | Javascript + | Json + | Jsx + | Markdown + | Python + | Ruby + | Typescript + | Php + deriving stock (Eq, Ord, Show, Enum, Bounded, Generic) + deriving anyclass (Named, MessageField, FromJSON, ToJSON) + deriving Primitive via PrimitiveEnum Language +instance HasDefault Language where def = Unknown diff --git a/src/Semantic/CLI.hs b/src/Semantic/CLI.hs index 39921d347..142a9bf4d 100644 --- a/src/Semantic/CLI.hs +++ b/src/Semantic/CLI.hs @@ -10,7 +10,7 @@ import Data.Handle import Data.Project import Options.Applicative hiding (style) import Prologue -import Semantic.API hiding (File) +import Semantic.Api hiding (File) import qualified Semantic.AST as AST import Semantic.Config import qualified Semantic.Graph as Graph diff --git a/test/Examples.hs b/test/Examples.hs index e15a1d94f..2855a33d8 100644 --- a/test/Examples.hs +++ b/test/Examples.hs @@ -17,7 +17,7 @@ import Data.Quieterm import Data.Typeable (cast) import Data.Void import Parsing.Parser -import Semantic.API (TermOutputFormat (..), parseTermBuilder) +import Semantic.Api (TermOutputFormat (..), parseTermBuilder) import Semantic.Config (Config (..), Options (..), defaultOptions) import qualified Semantic.IO as IO import Semantic.Task diff --git a/test/Rendering/TOC/Spec.hs b/test/Rendering/TOC/Spec.hs index 3b3b29a4d..4630ef7ca 100644 --- a/test/Rendering/TOC/Spec.hs +++ b/test/Rendering/TOC/Spec.hs @@ -24,7 +24,7 @@ import qualified Data.Syntax as Syntax import qualified Data.Syntax.Declaration as Declaration import Rendering.TOC import Semantic.Config -import Semantic.API (diffSummaryBuilder) +import Semantic.Api (diffSummaryBuilder) import Serializing.Format as Format import SpecHelpers diff --git a/test/Semantic/CLI/Spec.hs b/test/Semantic/CLI/Spec.hs index 1217896d9..2f6119109 100644 --- a/test/Semantic/CLI/Spec.hs +++ b/test/Semantic/CLI/Spec.hs @@ -4,7 +4,7 @@ import Control.Monad (when) import qualified Data.ByteString as B import Data.ByteString.Builder import Data.Foldable (for_) -import Semantic.API hiding (File, Blob, BlobPair) +import Semantic.Api hiding (File, Blob, BlobPair) import Semantic.CLI import Semantic.IO import Semantic.Task diff --git a/test/Semantic/Spec.hs b/test/Semantic/Spec.hs index 65e4f4130..a6f5674de 100644 --- a/test/Semantic/Spec.hs +++ b/test/Semantic/Spec.hs @@ -2,7 +2,7 @@ module Semantic.Spec (spec) where import Data.Diff import Data.Patch -import Semantic.API hiding (Blob) +import Semantic.Api hiding (Blob) import System.Exit import SpecHelpers diff --git a/test/SpecHelpers.hs b/test/SpecHelpers.hs index f2df8479b..5c8d48960 100644 --- a/test/SpecHelpers.hs +++ b/test/SpecHelpers.hs @@ -82,7 +82,7 @@ import Data.Set (Set) import qualified Semantic.IO as IO import Semantic.Config (Config(..), optionsLogLevel) import Semantic.Telemetry (LogQueue, StatQueue) -import Semantic.API hiding (File, Blob, BlobPair) +import Semantic.Api hiding (File, Blob, BlobPair) import System.Exit (die) import Control.Exception (displayException)