1
1
mirror of https://github.com/github/semantic.git synced 2024-11-23 08:27:56 +03:00

Introduce semantic-go

This commit is contained in:
Timothy Clem 2019-12-18 13:52:22 -08:00
parent 0593436131
commit 80ab58bd7f
16 changed files with 239 additions and 12 deletions

View File

@ -2,6 +2,7 @@ packages: .
semantic-analysis
semantic-ast
semantic-core
semantic-go
semantic-java
semantic-json
semantic-python

View File

@ -40,6 +40,7 @@ function flags {
echo "-isemantic-analysis/src"
echo "-isemantic-ast/src"
echo "-isemantic-core/src"
echo "-isemantic-go/src"
echo "-isemantic-java/src"
echo "-isemantic-json/src"
echo "-isemantic-python/src"

View File

@ -11,8 +11,9 @@ echo "semantic.cabal"
echo "semantic-analysis/semantic-analysis.cabal"
echo "semantic-ast/semantic-ast.cabal"
echo "semantic-core/semantic-core.cabal"
echo "semantic-tags/semantic-tags.cabal"
echo "semantic-go/semantic-go.cabal"
echo "semantic-java/semantic-java.cabal"
echo "semantic-json/semantic-json.cabal"
echo "semantic-python/semantic-python.cabal"
echo "semantic-ruby/semantic-ruby.cabal"
echo "semantic-tags/semantic-tags.cabal"

21
semantic-go/LICENSE Normal file
View File

@ -0,0 +1,21 @@
MIT License
Copyright (c) 2019 GitHub
Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
The above copyright notice and this permission notice shall be included in all
copies or substantial portions of the Software.
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
SOFTWARE.

3
semantic-go/README.md Normal file
View File

@ -0,0 +1,3 @@
# Semantic support for Go
This package implements `semantic` support for Go using the `semantic-core` intermediate language.

2
semantic-go/Setup.hs Normal file
View File

@ -0,0 +1,2 @@
import Distribution.Simple
main = defaultMain

View File

@ -0,0 +1,54 @@
cabal-version: 2.4
name: semantic-go
version: 0.0.0.0
synopsis: Semantic support for Go.
description: Semantic support for Go using the semantic-core intermediate language.
homepage: https://github.com/github/semantic/tree/master/semantic-go#readme
bug-reports: https://github.com/github/semantic/issues
license: MIT
license-file: LICENSE
author: The Semantic authors
maintainer: opensource+semantic@github.com
copyright: (c) 2019 GitHub, Inc.
category: Language
build-type: Simple
stability: alpha
extra-source-files: README.md
tested-with: GHC == 8.6.5
common haskell
default-language: Haskell2010
build-depends: base ^>= 4.13
, fused-effects ^>= 1.0
, fused-syntax
, parsers ^>= 0.12.10
, semantic-core ^>= 0.0
, semantic-source ^>= 0.0
, semantic-tags ^>= 0.0
, text ^>= 1.2.3
, tree-sitter ^>= 0.7.2
, tree-sitter-go ^>= 0.4
ghc-options:
-Weverything
-Wno-missing-local-signatures
-Wno-missing-import-lists
-Wno-implicit-prelude
-Wno-safe
-Wno-unsafe
-Wno-name-shadowing
-Wno-monomorphism-restriction
-Wno-missed-specialisations
-Wno-all-missed-specialisations
-Wno-star-is-type
if (impl(ghc >= 8.8))
ghc-options: -Wno-missing-deriving-strategies
library
import: haskell
exposed-modules:
Language.Go
Language.Go.Tags
hs-source-dirs: src

View File

@ -0,0 +1,20 @@
-- | Semantic functionality for Go programs.
module Language.Go
( Term(..)
, TreeSitter.Go.tree_sitter_go
) where
import qualified Language.Go.Tags as GoTags
import qualified Tags.Tagging.Precise as Tags
import qualified TreeSitter.Go (tree_sitter_go)
import qualified TreeSitter.Go.AST as Go
import qualified TreeSitter.Unmarshal as TS
newtype Term a = Term { getTerm :: Go.SourceFile a }
instance TS.Unmarshal Term where
unmarshalNode node = Term <$> TS.unmarshalNode node
instance Tags.ToTags Term where
tags src = Tags.runTagging src . GoTags.tags . getTerm

View File

@ -0,0 +1,96 @@
{-# LANGUAGE AllowAmbiguousTypes, DataKinds, DisambiguateRecordFields, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, NamedFieldPuns, OverloadedStrings, PartialTypeSignatures, ScopedTypeVariables, TypeApplications, TypeFamilies, TypeOperators, UndecidableInstances #-}
module Language.Go.Tags
( ToTags(..)
) where
import AST.Element
import Control.Effect.Reader
import Control.Effect.Writer
import Control.Monad
import Data.Monoid (Ap (..))
import Data.Foldable
import Data.Text as Text
import GHC.Generics
import Source.Loc
import Source.Source as Source
import Tags.Tag
import qualified Tags.Tagging.Precise as Tags
import qualified TreeSitter.Go.AST as Go
class ToTags t where
tags
:: ( Has (Reader Source) sig m
, Has (Writer Tags.Tags) sig m
)
=> t Loc
-> m ()
instance (ToTagsBy strategy t, strategy ~ ToTagsInstance t) => ToTags t where
tags = tags' @strategy
class ToTagsBy (strategy :: Strategy) t where
tags'
:: ( Has (Reader Source) sig m
, Has (Writer Tags.Tags) sig m
)
=> t Loc
-> m ()
data Strategy = Generic | Custom
type family ToTagsInstance t :: Strategy where
ToTagsInstance (_ :+: _) = 'Custom
ToTagsInstance Go.FunctionDeclaration = 'Custom
ToTagsInstance Go.MethodDeclaration = 'Custom
ToTagsInstance Go.CallExpression = 'Custom
ToTagsInstance _ = 'Generic
instance ToTagsBy 'Custom Go.FunctionDeclaration where
tags' t@Go.FunctionDeclaration
{ ann = loc@Loc { byteRange }
, name = Go.Identifier { text }
} = yieldTag text Function loc byteRange >> gtags t
instance ToTagsBy 'Custom Go.MethodDeclaration where
tags' t@Go.MethodDeclaration
{ ann = loc@Loc { byteRange }
, name = Go.FieldIdentifier { text }
} = yieldTag text Function loc byteRange >> gtags t
instance ToTagsBy 'Custom Go.CallExpression where
tags' t@Go.CallExpression
{ ann = loc@Loc { byteRange }
, function = Go.Expression expr
} = match expr
where
match expr = case expr of
Prj Go.SelectorExpression { field = Go.FieldIdentifier { text }} -> yield text
Prj Go.Identifier { text } -> yield text
Prj Go.CallExpression { function = Go.Expression e } -> match e
_ -> gtags t
yield name = yieldTag name Call loc byteRange >> gtags t
instance (ToTags l, ToTags r) => ToTagsBy 'Custom (l :+: r) where
tags' (L1 l) = tags l
tags' (R1 r) = tags r
gtags
:: ( Has (Reader Source) sig m
, Has (Writer Tags.Tags) sig m
, Generic1 t
, Tags.GFoldable1 ToTags (Rep1 t)
)
=> t Loc
-> m ()
gtags = getAp . Tags.gfoldMap1 @ToTags (Ap . tags) . from1
instance (Generic1 t, Tags.GFoldable1 ToTags (Rep1 t)) => ToTagsBy 'Generic t where
tags' = gtags
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> Kind -> Loc -> Range -> m ()
yieldTag name kind loc range = do
src <- ask @Source
let sliced = slice src range
Tags.yield (Tag name kind loc (Tags.firstLine sliced) Nothing)

View File

@ -285,6 +285,7 @@ library
, proto-lens-jsonpb
, proto-lens-runtime >= 0.5 && <0.7
, reducers ^>= 3.12.3
, semantic-go ^>= 0
, semantic-java ^>= 0
, semantic-json ^>= 0
, semantic-python ^>= 0

View File

@ -153,7 +153,7 @@ textToLanguage = \case
data PerLanguageModes = PerLanguageModes
{ pythonMode :: LanguageMode
, rubyMode :: LanguageMode
-- , typescriptMode :: LanguageMode
, goMode :: LanguageMode
}
deriving (Eq, Ord, Show)
@ -161,7 +161,7 @@ defaultLanguageModes :: PerLanguageModes
defaultLanguageModes = PerLanguageModes
{ pythonMode = ALaCarte
, rubyMode = ALaCarte
-- , typescriptMode = ALaCarte
, goMode = ALaCarte
}
data LanguageMode

View File

@ -5,6 +5,8 @@ module Parsing.Parser
-- $abstract
, SomeParser(..)
, goParser
, goParserALaCarte
, goParserPrecise
, javaParser
, javascriptParser
, jsonParser
@ -35,7 +37,8 @@ import qualified Data.Map as Map
import qualified Data.Syntax as Syntax
import Data.Term
import Foreign.Ptr
import qualified Language.Go.Assignment as Go
import qualified Language.Go as GoPrecise
import qualified Language.Go.Assignment as GoALaCarte
import qualified Language.Java as Java
import qualified Language.JSON as JSON
import qualified Language.Markdown.Assignment as Markdown
@ -103,8 +106,16 @@ data Parser term where
data SomeParser c a where
SomeParser :: c t => Parser (t a) -> SomeParser c a
goParser :: c Go.Term => (Language, SomeParser c Loc)
goParser = (Go, SomeParser (AssignmentParser (ASTParser tree_sitter_go) Go.assignment))
goParserALaCarte :: c GoALaCarte.Term => (Language, SomeParser c Loc)
goParserALaCarte = (Go, SomeParser (AssignmentParser (ASTParser tree_sitter_go) GoALaCarte.assignment))
goParserPrecise :: c GoPrecise.Term => (Language, SomeParser c Loc)
goParserPrecise = (Go, SomeParser (UnmarshalParser @GoPrecise.Term GoPrecise.tree_sitter_go))
goParser :: (c GoALaCarte.Term, c GoPrecise.Term) => PerLanguageModes -> (Language, SomeParser c Loc)
goParser modes = case goMode modes of
ALaCarte -> goParserALaCarte
Precise -> goParserPrecise
javaParser :: c Java.Term => (Language, SomeParser c Loc)
javaParser = (Java, SomeParser (UnmarshalParser @Java.Term Java.tree_sitter_java))
@ -155,6 +166,7 @@ typescriptParser = (TypeScript, SomeParser (AssignmentParser (ASTParser tree_sit
-- | A type family selecting the language mode for a given term type.
type family TermMode term where
TermMode GoPrecise.Term = 'Precise
TermMode Java.Term = 'Precise
TermMode JSON.Term = 'Precise
TermMode PythonPrecise.Term = 'Precise
@ -164,7 +176,7 @@ type family TermMode term where
-- | The canonical set of parsers producing à la carte terms.
aLaCarteParsers
:: ( c Go.Term
:: ( c GoALaCarte.Term
, c Markdown.Term
, c PHP.Term
, c PythonALaCarte.Term
@ -174,7 +186,7 @@ aLaCarteParsers
)
=> Map Language (SomeParser c Loc)
aLaCarteParsers = Map.fromList
[ goParser
[ goParserALaCarte
, javascriptParser
, jsxParser
, markdownParser
@ -191,6 +203,7 @@ preciseParsers
, c JSON.Term
, c PythonPrecise.Term
, c RubyPrecise.Term
, c GoPrecise.Term
)
=> Map Language (SomeParser c Loc)
preciseParsers = Map.fromList
@ -198,11 +211,13 @@ preciseParsers = Map.fromList
, jsonParser
, pythonParserPrecise
, rubyParserPrecise
, goParserPrecise
]
-- | The canonical set of all parsers for the passed per-language modes.
allParsers
:: ( c Go.Term
:: ( c GoALaCarte.Term
, c GoPrecise.Term
, c Java.Term
, c JSON.Term
, c Markdown.Term
@ -217,7 +232,7 @@ allParsers
=> PerLanguageModes
-> Map Language (SomeParser c Loc)
allParsers modes = Map.fromList
[ goParser
[ goParser modes
, javaParser
, javascriptParser
, jsonParser

View File

@ -40,6 +40,7 @@ import Source.Loc
import qualified Language.Java as Java
import qualified Language.JSON as JSON
import qualified Language.Go as GoPrecise
import qualified Language.Python as PythonPrecise
import qualified Language.Ruby as RubyPrecise
@ -108,6 +109,9 @@ instance (TermMode term ~ strategy, ShowTermBy strategy term) => ShowTerm term w
class ShowTermBy (strategy :: LanguageMode) term where
showTermBy :: (Has (Reader Config) sig m) => term Loc -> m Builder
instance ShowTermBy 'Precise GoPrecise.Term where
showTermBy = serialize Show . void . GoPrecise.getTerm
instance ShowTermBy 'Precise Java.Term where
showTermBy = serialize Show . void . Java.getTerm
@ -136,6 +140,9 @@ instance (TermMode term ~ strategy, SExprTermBy strategy term) => SExprTerm term
class SExprTermBy (strategy :: LanguageMode) term where
sexprTermBy :: term Loc -> Builder
instance SExprTermBy 'Precise GoPrecise.Term where
sexprTermBy = SExpr.Precise.serializeSExpression . GoPrecise.getTerm
instance SExprTermBy 'Precise Java.Term where
sexprTermBy = SExpr.Precise.serializeSExpression . Java.getTerm

View File

@ -178,6 +178,11 @@ languageModes = Language.PerLanguageModes
<> metavar "ALaCarte|Precise"
<> value Language.ALaCarte
<> showDefault)
<*> option auto ( long "go-mode"
<> help "The AST representation to use for Go sources"
<> metavar "ALaCarte|Precise"
<> value Language.ALaCarte
<> showDefault)
filePathReader :: ReadM File
filePathReader = fileForPath <$> str

View File

@ -104,7 +104,7 @@ instance
analysisParsers :: Map Language (SomeParser AnalyzeTerm Loc)
analysisParsers = Map.fromList
[ goParser
[ goParserALaCarte
, javascriptParser
, phpParser
, pythonParserALaCarte

View File

@ -63,7 +63,7 @@ parseFixtures =
path' = [File "test/fixtures/ruby/corpus/and-or.A.rb" Ruby, File "test/fixtures/ruby/corpus/and-or.B.rb" Ruby]
path'' = [File "test/fixtures/ruby/corpus/method-declaration.A.rb" Ruby]
prefix = Path.relDir "test/fixtures/cli"
run = runReader (PerLanguageModes ALaCarte ALaCarte)
run = runReader defaultLanguageModes
diffFixtures :: [(String, [BlobPair] -> ParseC TaskC Builder, [(File, File)], Path.RelFile)]
diffFixtures =