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

Remove some un-used code

This commit is contained in:
Timothy Clem 2019-01-25 10:12:38 -08:00
parent a6f5bfd77f
commit 1faff05a2b
5 changed files with 1 additions and 243 deletions

View File

@ -90,8 +90,6 @@ library
, Data.Language
, Data.Location
, Data.Map.Monoidal
, Data.Proto.DiffTree
, Data.Proto.ParseTree
, Data.Patch
, Data.Project
, Data.Quieterm

View File

@ -1,92 +0,0 @@
{-# LANGUAGE DeriveAnyClass #-}
module Data.Proto.DiffTree (DiffTree(..), ResponseType(..)) where
import Prologue
import Data.Language
import Data.Diff
import qualified Language.Go.Assignment as Go
import qualified Language.Haskell.Assignment as Haskell
import qualified Language.Java.Assignment as Java
import qualified Language.JSON.Assignment as JSON
import qualified Language.Markdown.Assignment as Markdown
import qualified Language.PHP.Assignment as PHP
import qualified Language.Python.Assignment as Python
import qualified Language.Ruby.Assignment as Ruby
import qualified Language.TypeScript.Assignment as TypeScript
import Proto3.Suite
import qualified Proto3.Suite as PB
import qualified Proto3.Wire.Encode as Encode
type GoDiff = Diff (Sum Go.Syntax) () ()
type HaskellDiff = Diff (Sum Haskell.Syntax) () ()
type JavaDiff = Diff (Sum Java.Syntax) () ()
type JSONDiff = Diff (Sum JSON.Syntax) () ()
type MarkdownDiff = Diff (Sum Markdown.Syntax) () ()
type PythonDiff = Diff (Sum Python.Syntax) () ()
type RubyDiff = Diff (Sum Ruby.Syntax) () ()
type TypeScriptDiff = Diff (Sum TypeScript.Syntax) () ()
type PHPDiff = Diff (Sum PHP.Syntax) () ()
data DiffTree
= DiffTree
{ languageBefore :: Language
, languageAfter :: Language
, pathBefore :: FilePath
, pathAfter :: FilePath
, responseType :: Maybe ResponseType
} deriving (Eq, Show, Generic, Named)
data ResponseType
= ParseDiffError String
| GoDiffResponse GoDiff
| HaskellDiffResponse HaskellDiff
| JavaDiffResponse JavaDiff
| JSONDiffResponse JSONDiff
| MarkdownDiffResponse MarkdownDiff
| PythonDiffResponse PythonDiff
| RubyDiffResponse RubyDiff
| TypeScriptDiffResponse TypeScriptDiff
| PHPDiffResponse PHPDiff
deriving (Eq, Show)
-- Instances
instance Message DiffTree where
encodeMessage _ DiffTree{..}
= encodeMessageField 1 languageBefore
<> encodeMessageField 2 languageAfter
<> encodeMessageField 3 pathBefore
<> encodeMessageField 4 pathAfter
<> case responseType of
Just (ParseDiffError x) -> Encode.embedded 5 (encodeMessageField 1 x)
Just (GoDiffResponse x) -> Encode.embedded 6 (encodeMessage 1 x)
Just (HaskellDiffResponse x) -> Encode.embedded 7 (encodeMessage 1 x)
Just (JavaDiffResponse x) -> Encode.embedded 8 (encodeMessage 1 x)
Just (JSONDiffResponse x) -> Encode.embedded 9 (encodeMessage 1 x)
Just (MarkdownDiffResponse x) -> Encode.embedded 10 (encodeMessage 1 x)
Just (PythonDiffResponse x) -> Encode.embedded 11 (encodeMessage 1 x)
Just (RubyDiffResponse x) -> Encode.embedded 12 (encodeMessage 1 x)
Just (TypeScriptDiffResponse x) -> Encode.embedded 13 (encodeMessage 1 x)
Just (PHPDiffResponse x) -> Encode.embedded 14 (encodeMessage 1 x)
_ -> mempty
decodeMessage = error "decodeMessage not implemented for DiffTree"
dotProto _ =
[ DotProtoMessageField $ DotProtoField 1 (Prim . Named $ Single "Language") (Single "language_before") [] Nothing
, DotProtoMessageField $ DotProtoField 2 (Prim . Named $ Single "Language") (Single "language_after") [] Nothing
, DotProtoMessageField $ DotProtoField 3 (Prim PB.String) (Single "path_before") [] Nothing
, DotProtoMessageField $ DotProtoField 4 (Prim PB.String) (Single "path_after") [] Nothing
, DotProtoMessageOneOf (Single "response_type")
[ DotProtoField 5 (Prim PB.String) (Single "error") [] Nothing
, DotProtoField 6 (Prim . Named $ Dots (Path ["godiff", "GoDiff"])) (Single "go_diff") [] Nothing
, DotProtoField 7 (Prim . Named $ Dots (Path ["haskelldiff", "HaskellDiff"])) (Single "haskell_diff") [] Nothing
, DotProtoField 8 (Prim . Named $ Dots (Path ["javadiff", "JavaDiff"])) (Single "java_diff") [] Nothing
, DotProtoField 9 (Prim . Named $ Dots (Path ["jsondiff", "JSONDiff"])) (Single "json_diff") [] Nothing
, DotProtoField 10 (Prim . Named $ Dots (Path ["markdowndiff", "MarkdownDiff"])) (Single "markdown_diff") [] Nothing
, DotProtoField 11 (Prim . Named $ Dots (Path ["pythondiff", "PythonDiff"])) (Single "python_diff") [] Nothing
, DotProtoField 12 (Prim . Named $ Dots (Path ["rubydiff", "RubyDiff"])) (Single "ruby_diff") [] Nothing
, DotProtoField 13 (Prim . Named $ Dots (Path ["typescriptdiff", "TypeScriptDiff"])) (Single "typescript_diff") [] Nothing
, DotProtoField 14 (Prim . Named $ Dots (Path ["phpdiff", "PHPDiff"])) (Single "php_diff") [] Nothing
]
]

View File

@ -1,86 +0,0 @@
{-# LANGUAGE DeriveAnyClass #-}
module Data.Proto.ParseTree (ParseTree(..), ResponseType(..)) where
import Prologue
import Data.Language
import Data.Term
import qualified Language.Go.Assignment as Go
import qualified Language.Haskell.Assignment as Haskell
import qualified Language.Java.Assignment as Java
import qualified Language.JSON.Assignment as JSON
import qualified Language.Markdown.Assignment as Markdown
import qualified Language.PHP.Assignment as PHP
import qualified Language.Python.Assignment as Python
import qualified Language.Ruby.Assignment as Ruby
import qualified Language.TypeScript.Assignment as TypeScript
import Proto3.Suite
import qualified Proto3.Suite as PB
import qualified Proto3.Wire.Encode as Encode
type GoTerm = Term (Sum Go.Syntax) ()
type HaskellTerm = Term (Sum Haskell.Syntax) ()
type JavaTerm = Term (Sum Java.Syntax) ()
type JSONTerm = Term (Sum JSON.Syntax) ()
type MarkdownTerm = Term (Sum Markdown.Syntax) ()
type PythonTerm = Term (Sum Python.Syntax) ()
type RubyTerm = Term (Sum Ruby.Syntax) ()
type TypeScriptTerm = Term (Sum TypeScript.Syntax) ()
type PHPTerm = Term (Sum PHP.Syntax) ()
data ParseTree
= ParseTree
{ language :: Language
, path :: FilePath
, responseType :: Maybe ResponseType
} deriving (Eq, Show, Generic, Named)
data ResponseType
= ParseError String
| GoResponse GoTerm
| HaskellResponse HaskellTerm
| JavaResponse JavaTerm
| JSONResponse JSONTerm
| MarkdownResponse MarkdownTerm
| PythonResponse PythonTerm
| RubyResponse RubyTerm
| TypeScriptResponse TypeScriptTerm
| PHPResponse PHPTerm
deriving (Eq, Show)
-- Instances
instance Message ParseTree where
encodeMessage _ ParseTree{..}
= encodeMessageField 1 language
<> encodeMessageField 2 path
<> case responseType of
Just (ParseError x) -> Encode.embedded 3 (encodeMessageField 1 x)
Just (GoResponse x) -> Encode.embedded 4 (encodeMessage 1 x)
Just (HaskellResponse x) -> Encode.embedded 5 (encodeMessage 1 x)
Just (JavaResponse x) -> Encode.embedded 6 (encodeMessage 1 x)
Just (JSONResponse x) -> Encode.embedded 7 (encodeMessage 1 x)
Just (MarkdownResponse x) -> Encode.embedded 8 (encodeMessage 1 x)
Just (PythonResponse x) -> Encode.embedded 9 (encodeMessage 1 x)
Just (RubyResponse x) -> Encode.embedded 10 (encodeMessage 1 x)
Just (TypeScriptResponse x) -> Encode.embedded 11 (encodeMessage 1 x)
Just (PHPResponse x) -> Encode.embedded 12 (encodeMessage 1 x)
_ -> mempty
decodeMessage = error "decodeMessage not implemented for ParseTree"
dotProto _ =
[ DotProtoMessageField $ DotProtoField 1 (Prim . Named $ Single "Language") (Single "language") [] Nothing
, DotProtoMessageField $ DotProtoField 2 (Prim PB.String) (Single "path") [] Nothing
, DotProtoMessageOneOf (Single "response_type")
[ DotProtoField 3 (Prim PB.String) (Single "error") [] Nothing
, DotProtoField 4 (Prim . Named $ Dots (Path ["goterm", "GoTerm"])) (Single "go_tree") [] Nothing
, DotProtoField 5 (Prim . Named $ Dots (Path ["haskellterm", "HaskellTerm"])) (Single "haskell_tree") [] Nothing
, DotProtoField 6 (Prim . Named $ Dots (Path ["javaterm", "JavaTerm"])) (Single "java_tree") [] Nothing
, DotProtoField 7 (Prim . Named $ Dots (Path ["jsonterm", "JSONTerm"])) (Single "json_tree") [] Nothing
, DotProtoField 8 (Prim . Named $ Dots (Path ["markdownterm", "MarkdownTerm"])) (Single "markdown_tree") [] Nothing
, DotProtoField 9 (Prim . Named $ Dots (Path ["pythonterm", "PythonTerm"])) (Single "python_tree") [] Nothing
, DotProtoField 10 (Prim . Named $ Dots (Path ["rubyterm", "RubyTerm"])) (Single "ruby_tree") [] Nothing
, DotProtoField 11 (Prim . Named $ Dots (Path ["typescriptterm", "TypeScriptTerm"])) (Single "typescript_tree") [] Nothing
, DotProtoField 12 (Prim . Named $ Dots (Path ["phpterm", "PHPTerm"])) (Single "php_tree") [] Nothing
]
]

View File

@ -3,11 +3,8 @@ module Parsing.Parser
( Parser(..)
, SomeTerm(..)
, withSomeTerm
, SomeSyntaxTerm
, withSomeSyntaxTerm
, SomeAnalysisParser(..)
, SomeASTParser(..)
, someParser
, someASTParser
, someAnalysisParser
, ApplyAll
@ -124,36 +121,6 @@ type family ApplyAll (typeclasses :: [(* -> *) -> Constraint]) (syntax :: * -> *
ApplyAll (typeclass ': typeclasses) syntax = (typeclass syntax, ApplyAll typeclasses syntax)
ApplyAll '[] syntax = ()
-- | Construct a 'Parser' given a proxy for a list of typeclasses and the 'Language' to be parsed, all of which must be satisfied by all of the types in the syntaxes of our supported languages.
--
-- This can be used to perform operations uniformly over terms produced by blobs with different 'Language's, and which therefore have different types in general. For example, given some 'Blob', we can parse and 'show' the parsed & assigned 'Term' like so:
--
-- > runTask (parse (someParser @'[Show1] language) blob) >>= putStrLn . withSomeTerm show
someParser :: ( ApplyAll typeclasses (Sum Go.Syntax)
, ApplyAll typeclasses (Sum Haskell.Syntax)
, ApplyAll typeclasses (Sum Java.Syntax)
, ApplyAll typeclasses (Sum JSON.Syntax)
, ApplyAll typeclasses (Sum Markdown.Syntax)
, ApplyAll typeclasses (Sum Python.Syntax)
, ApplyAll typeclasses (Sum Ruby.Syntax)
, ApplyAll typeclasses (Sum TypeScript.Syntax)
, ApplyAll typeclasses (Sum PHP.Syntax)
)
=> Language -- ^ The 'Language' to select.
-> Maybe (Parser (SomeTerm typeclasses Location)) -- ^ A 'SomeParser' abstracting the syntax type to be produced.
someParser Go = Just (SomeParser goParser)
someParser Java = Just (SomeParser javaParser)
someParser JavaScript = Just (SomeParser typescriptParser)
someParser JSON = Just (SomeParser jsonParser)
someParser Haskell = Just (SomeParser haskellParser)
someParser JSX = Just (SomeParser typescriptParser)
someParser Markdown = Just (SomeParser markdownParser)
someParser Python = Just (SomeParser pythonParser)
someParser Ruby = Just (SomeParser rubyParser)
someParser TypeScript = Just (SomeParser typescriptParser)
someParser PHP = Just (SomeParser phpParser)
someParser Unknown = Nothing
goParser :: Parser Go.Term
goParser = AssignmentParser (ASTParser tree_sitter_go) Go.assignment
@ -201,12 +168,6 @@ data SomeTerm typeclasses ann where
withSomeTerm :: (forall syntax . ApplyAll typeclasses syntax => Term syntax ann -> a) -> SomeTerm typeclasses ann -> a
withSomeTerm with (SomeTerm term) = with term
data SomeSyntaxTerm syntax ann where
SomeSyntaxTerm :: Term syntax ann -> SomeSyntaxTerm syntax ann
withSomeSyntaxTerm :: (forall syntax . Term syntax ann -> a) -> SomeSyntaxTerm syntax ann -> a
withSomeSyntaxTerm with (SomeSyntaxTerm term) = with term
-- | A parser for producing specialized (tree-sitter) ASTs.
data SomeASTParser where
SomeASTParser :: (Bounded grammar, Enum grammar, Show grammar)

View File

@ -1,9 +1,7 @@
{-# LANGUAGE DerivingVia, DerivingStrategies, DeriveAnyClass, RankNTypes, ScopedTypeVariables #-}
{-# LANGUAGE DerivingVia, DerivingStrategies, RankNTypes, ScopedTypeVariables #-}
module Rendering.TOC
( renderToCDiff
, renderRPCToCDiff
, renderToCTerm
, renderJSONSummaryError
, diffTOC
, Summaries(..)
, TOCSummary(..)
@ -31,15 +29,9 @@ import Data.Patch
import Data.Location
import Data.Term
import qualified Data.Text as T
import Proto3.Suite as Proto3
renderJSONSummaryError :: BlobPair -> String -> Summaries
renderJSONSummaryError pair e = Summaries mempty (Map.singleton path [object ["error" .= e]])
where path = T.pack (pathKeyForBlobPair pair)
data Summaries = Summaries { changes, errors :: Map.Map T.Text [Value] }
deriving stock (Eq, Show, Generic)
deriving anyclass (Named)
deriving Semigroup via GenericSemigroup Summaries
deriving Monoid via GenericMonoid Summaries
@ -55,18 +47,6 @@ data TOCSummary
}
| ErrorSummary { errorText :: T.Text, errorSpan :: Span, errorLanguage :: Language }
deriving stock (Generic, Eq, Show)
deriving anyclass (Named)
-- TODO: Get this to auto generate. The following is incomplete.
instance Message TOCSummary where
encodeMessage = undefined
decodeMessage = undefined
dotProto _ =
[ DotProtoMessageField $ DotProtoField 1 (Prim Proto3.String) (Single "summaryCategoryName") [] Nothing
, DotProtoMessageField $ DotProtoField 1 (Prim Proto3.String) (Single "summaryTermName") [] Nothing
, DotProtoMessageField $ DotProtoField 1 (Prim . Named $ Single "Span") (Single "summarySpan") [] Nothing
, DotProtoMessageField $ DotProtoField 1 (Prim Proto3.String) (Single "summaryChangeType") [] Nothing
]
instance ToJSON TOCSummary where
toJSON TOCSummary{..} = object [ "changeType" .= summaryChangeType, "category" .= summaryCategoryName, "term" .= summaryTermName, "span" .= summarySpan ]
@ -160,9 +140,6 @@ renderToCDiff blobs = uncurry Summaries . bimap toMap toMap . List.partition isV
toMap as = Map.singleton summaryKey (toJSON <$> as)
summaryKey = T.pack $ pathKeyForBlobPair blobs
renderRPCToCDiff :: (Foldable f, Functor f) => BlobPair -> Diff f (Maybe Declaration) (Maybe Declaration) -> ([TOCSummary], [TOCSummary])
renderRPCToCDiff _ = List.partition isValidSummary . diffTOC
diffTOC :: (Foldable f, Functor f) => Diff f (Maybe Declaration) (Maybe Declaration) -> [TOCSummary]
diffTOC = fmap entrySummary . dedupe . tableOfContentsBy declaration