mirror of
https://github.com/github/semantic.git
synced 2024-12-27 17:05:33 +03:00
Fully commit to new method of generating symbols
This commit is contained in:
parent
0a9034e28f
commit
fa60a394b4
@ -12,7 +12,6 @@ module Rendering.Renderer
|
||||
, renderToCTerm
|
||||
, renderSymbolTerms
|
||||
, renderToSymbols
|
||||
, renderToSymbols'
|
||||
, renderTreeGraph
|
||||
, renderJSONError
|
||||
, Summaries(..)
|
||||
|
@ -1,39 +1,31 @@
|
||||
{-# LANGUAGE RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
module Rendering.Symbol
|
||||
( renderToSymbols
|
||||
, renderToSymbols'
|
||||
, SymbolFields(..)
|
||||
, defaultSymbolFields
|
||||
, parseSymbolFields
|
||||
) where
|
||||
|
||||
import Prologue hiding (when)
|
||||
import Analysis.Declaration
|
||||
import Data.Aeson
|
||||
import Data.Blob
|
||||
import Data.Language (ensureLanguage)
|
||||
import Data.Location
|
||||
import Data.List.Split (splitWhen)
|
||||
import Data.Term
|
||||
|
||||
import Data.Aeson
|
||||
import Data.Blob
|
||||
import Data.List.Split (splitWhen)
|
||||
import Data.Location
|
||||
import Data.Term
|
||||
import qualified Data.Text as T
|
||||
import Rendering.TOC
|
||||
import Tags.Tagging
|
||||
import Tags.Taggable
|
||||
import Tags.Taggable
|
||||
import Tags.Tagging
|
||||
|
||||
|
||||
-- | Render a 'Term' to a list of symbols (See 'Symbol').
|
||||
renderToSymbols :: (Foldable f, Functor f) => SymbolFields -> Blob -> Term f (Maybe Declaration) -> [Value]
|
||||
renderToSymbols fields Blob{..} term = [toJSON (termToC fields blobPath term)]
|
||||
where
|
||||
termToC :: (Foldable f, Functor f) => SymbolFields -> FilePath -> Term f (Maybe Declaration) -> File
|
||||
termToC fields path = File (T.pack path) (T.pack (show blobLanguage)) . mapMaybe (symbolSummary fields path "unchanged") . termTableOfContentsBy declaration
|
||||
|
||||
renderToSymbols' :: (IsTaggable f) => SymbolFields -> Blob -> Term f Location -> [File]
|
||||
renderToSymbols' fields blob term = either mempty (pure . tagsToFile fields blob) (runTagging blob term)
|
||||
renderToSymbols :: (IsTaggable f) => SymbolFields -> Blob -> Term f Location -> [File]
|
||||
renderToSymbols fields blob term = either mempty (pure . tagsToFile fields blob) (runTagging blob term)
|
||||
|
||||
tagsToFile :: SymbolFields -> Blob -> [Tag] -> File
|
||||
tagsToFile fields blob@Blob{..} tags = File (T.pack blobPath) (T.pack (show blobLanguage)) (fmap (tagToSymbol fields blob) tags)
|
||||
|
||||
-- | Construct a 'Symbol' from a 'Tag'
|
||||
tagToSymbol :: SymbolFields -> Blob -> Tag -> Symbol
|
||||
tagToSymbol SymbolFields{..} Blob{..} Tag{..}
|
||||
= Symbol
|
||||
@ -46,20 +38,6 @@ tagToSymbol SymbolFields{..} Blob{..} Tag{..}
|
||||
, symbolDocs = join (when symbolFieldsDocs docs)
|
||||
}
|
||||
|
||||
-- | Construct a 'Symbol' from a node annotation and a change type label.
|
||||
symbolSummary :: SymbolFields -> FilePath -> T.Text -> Declaration -> Maybe Symbol
|
||||
symbolSummary SymbolFields{..} path _ record = case record of
|
||||
ErrorDeclaration{} -> Nothing
|
||||
declaration -> Just Symbol
|
||||
{ symbolName = when symbolFieldsName (declarationIdentifier declaration)
|
||||
, symbolPath = when symbolFieldsPath (T.pack path)
|
||||
, symbolLang = join (when symbolFieldsLang (T.pack . show <$> ensureLanguage (declarationLanguage declaration)))
|
||||
, symbolKind = when symbolFieldsKind (toCategoryName declaration)
|
||||
, symbolLine = when symbolFieldsLine (declarationText declaration)
|
||||
, symbolSpan = when symbolFieldsSpan (declarationSpan declaration)
|
||||
, symbolDocs = Nothing
|
||||
}
|
||||
|
||||
data File = File
|
||||
{ filePath :: T.Text
|
||||
, fileLanguage :: T.Text
|
||||
|
@ -2,7 +2,6 @@
|
||||
module Semantic.Parse ( runParse, runParse', parseSomeBlob ) where
|
||||
|
||||
import Analysis.ConstructorName (ConstructorName)
|
||||
import Analysis.Declaration (HasDeclaration, declarationAlgebra)
|
||||
import Analysis.PackageDef (HasPackageDef)
|
||||
import Control.Effect
|
||||
import Control.Effect.Error
|
||||
@ -34,8 +33,7 @@ runParse JSONGraphTermRenderer = withParsedBlobs' renderJSONError (render
|
||||
renderAdjGraph blob term = renderJSONAdjTerm blob (renderTreeGraph term)
|
||||
runParse SExpressionTermRenderer = withParsedBlobs (const (serialize (SExpression ByConstructorName)))
|
||||
runParse ShowTermRenderer = withParsedBlobs (const (serialize Show . quieterm))
|
||||
runParse (SymbolsTermRenderer fields) = withParsedBlobs (\ blob -> render (renderSymbolTerms . renderToSymbols' fields blob)) >=> serialize JSON
|
||||
-- runParse (SymbolsTermRenderer fields) = withParsedBlobs (\ blob -> decorate (declarationAlgebra blob) >=> render (renderSymbolTerms . renderToSymbols fields blob)) >=> serialize JSON
|
||||
runParse (SymbolsTermRenderer fields) = withParsedBlobs (\ blob -> render (renderSymbolTerms . renderToSymbols fields blob)) >=> serialize JSON
|
||||
runParse DOTTermRenderer = withParsedBlobs (const (render renderTreeGraph)) >=> serialize (DOT (termStyle "terms"))
|
||||
runParse QuietTermRenderer = distributeFoldMap $ \blob ->
|
||||
showTiming blob <$> time' ((parseSomeBlob blob >>= withSomeTerm (fmap (const (Right ())) . serialize Show . quieterm)) `catchError` \(SomeException e) -> pure (Left (show e)))
|
||||
@ -51,7 +49,6 @@ runParse' blob = parseSomeBlob blob >>= withSomeTerm (serialize Show . quieterm)
|
||||
type Render m output
|
||||
= forall syntax
|
||||
. ( ConstructorName syntax
|
||||
, HasDeclaration syntax
|
||||
, HasPackageDef syntax
|
||||
, Foldable syntax
|
||||
, Functor syntax
|
||||
@ -75,5 +72,5 @@ withParsedBlobs' onError render = distributeFoldMap $ \blob ->
|
||||
(parseSomeBlob blob >>= withSomeTerm (render blob)) `catchError` \(SomeException e) ->
|
||||
pure (onError blob (show e))
|
||||
|
||||
parseSomeBlob :: (Member (Error SomeException) sig, Member Task sig, Carrier sig m) => Blob -> m (SomeTerm '[ConstructorName, Foldable, Functor, HasDeclaration, HasPackageDef, Show1, ToJSONFields1, Taggable, HasTextElement, Declarations1] Location)
|
||||
parseSomeBlob :: (Member (Error SomeException) sig, Member Task sig, Carrier sig m) => Blob -> m (SomeTerm '[ConstructorName, Foldable, Functor, HasPackageDef, Show1, ToJSONFields1, Taggable, HasTextElement, Declarations1] Location)
|
||||
parseSomeBlob blob@Blob{..} = maybe (noLanguageForBlob blobPath) (`parse` blob) (someParser blobLanguage)
|
||||
|
Loading…
Reference in New Issue
Block a user