Skip to content

Commit 80ab58b

Browse files
committed
Introduce semantic-go
1 parent 0593436 commit 80ab58b

File tree

16 files changed

+239
-12
lines changed

16 files changed

+239
-12
lines changed

cabal.project

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@ packages: .
22
semantic-analysis
33
semantic-ast
44
semantic-core
5+
semantic-go
56
semantic-java
67
semantic-json
78
semantic-python

script/ghci-flags

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,7 @@ function flags {
4040
echo "-isemantic-analysis/src"
4141
echo "-isemantic-ast/src"
4242
echo "-isemantic-core/src"
43+
echo "-isemantic-go/src"
4344
echo "-isemantic-java/src"
4445
echo "-isemantic-json/src"
4546
echo "-isemantic-python/src"

script/ghci-flags-dependencies

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,8 +11,9 @@ echo "semantic.cabal"
1111
echo "semantic-analysis/semantic-analysis.cabal"
1212
echo "semantic-ast/semantic-ast.cabal"
1313
echo "semantic-core/semantic-core.cabal"
14+
echo "semantic-tags/semantic-tags.cabal"
15+
echo "semantic-go/semantic-go.cabal"
1416
echo "semantic-java/semantic-java.cabal"
1517
echo "semantic-json/semantic-json.cabal"
1618
echo "semantic-python/semantic-python.cabal"
1719
echo "semantic-ruby/semantic-ruby.cabal"
18-
echo "semantic-tags/semantic-tags.cabal"

semantic-go/LICENSE

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

semantic-go/README.md

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
# Semantic support for Go
2+
3+
This package implements `semantic` support for Go using the `semantic-core` intermediate language.

semantic-go/Setup.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
import Distribution.Simple
2+
main = defaultMain

semantic-go/semantic-go.cabal

Lines changed: 54 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,54 @@
1+
cabal-version: 2.4
2+
3+
name: semantic-go
4+
version: 0.0.0.0
5+
synopsis: Semantic support for Go.
6+
description: Semantic support for Go using the semantic-core intermediate language.
7+
homepage: https://github.com/github/semantic/tree/master/semantic-go#readme
8+
bug-reports: https://github.com/github/semantic/issues
9+
license: MIT
10+
license-file: LICENSE
11+
author: The Semantic authors
12+
maintainer: [email protected]
13+
copyright: (c) 2019 GitHub, Inc.
14+
category: Language
15+
build-type: Simple
16+
stability: alpha
17+
extra-source-files: README.md
18+
19+
tested-with: GHC == 8.6.5
20+
21+
common haskell
22+
default-language: Haskell2010
23+
build-depends: base ^>= 4.13
24+
, fused-effects ^>= 1.0
25+
, fused-syntax
26+
, parsers ^>= 0.12.10
27+
, semantic-core ^>= 0.0
28+
, semantic-source ^>= 0.0
29+
, semantic-tags ^>= 0.0
30+
, text ^>= 1.2.3
31+
, tree-sitter ^>= 0.7.2
32+
, tree-sitter-go ^>= 0.4
33+
34+
ghc-options:
35+
-Weverything
36+
-Wno-missing-local-signatures
37+
-Wno-missing-import-lists
38+
-Wno-implicit-prelude
39+
-Wno-safe
40+
-Wno-unsafe
41+
-Wno-name-shadowing
42+
-Wno-monomorphism-restriction
43+
-Wno-missed-specialisations
44+
-Wno-all-missed-specialisations
45+
-Wno-star-is-type
46+
if (impl(ghc >= 8.8))
47+
ghc-options: -Wno-missing-deriving-strategies
48+
49+
library
50+
import: haskell
51+
exposed-modules:
52+
Language.Go
53+
Language.Go.Tags
54+
hs-source-dirs: src

semantic-go/src/Language/Go.hs

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
-- | Semantic functionality for Go programs.
2+
module Language.Go
3+
( Term(..)
4+
, TreeSitter.Go.tree_sitter_go
5+
) where
6+
7+
8+
import qualified Language.Go.Tags as GoTags
9+
import qualified Tags.Tagging.Precise as Tags
10+
import qualified TreeSitter.Go (tree_sitter_go)
11+
import qualified TreeSitter.Go.AST as Go
12+
import qualified TreeSitter.Unmarshal as TS
13+
14+
newtype Term a = Term { getTerm :: Go.SourceFile a }
15+
16+
instance TS.Unmarshal Term where
17+
unmarshalNode node = Term <$> TS.unmarshalNode node
18+
19+
instance Tags.ToTags Term where
20+
tags src = Tags.runTagging src . GoTags.tags . getTerm

semantic-go/src/Language/Go/Tags.hs

Lines changed: 96 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,96 @@
1+
{-# LANGUAGE AllowAmbiguousTypes, DataKinds, DisambiguateRecordFields, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, NamedFieldPuns, OverloadedStrings, PartialTypeSignatures, ScopedTypeVariables, TypeApplications, TypeFamilies, TypeOperators, UndecidableInstances #-}
2+
module Language.Go.Tags
3+
( ToTags(..)
4+
) where
5+
6+
import AST.Element
7+
import Control.Effect.Reader
8+
import Control.Effect.Writer
9+
import Control.Monad
10+
import Data.Monoid (Ap (..))
11+
import Data.Foldable
12+
import Data.Text as Text
13+
import GHC.Generics
14+
import Source.Loc
15+
import Source.Source as Source
16+
import Tags.Tag
17+
import qualified Tags.Tagging.Precise as Tags
18+
import qualified TreeSitter.Go.AST as Go
19+
20+
class ToTags t where
21+
tags
22+
:: ( Has (Reader Source) sig m
23+
, Has (Writer Tags.Tags) sig m
24+
)
25+
=> t Loc
26+
-> m ()
27+
28+
instance (ToTagsBy strategy t, strategy ~ ToTagsInstance t) => ToTags t where
29+
tags = tags' @strategy
30+
31+
32+
class ToTagsBy (strategy :: Strategy) t where
33+
tags'
34+
:: ( Has (Reader Source) sig m
35+
, Has (Writer Tags.Tags) sig m
36+
)
37+
=> t Loc
38+
-> m ()
39+
40+
41+
data Strategy = Generic | Custom
42+
43+
type family ToTagsInstance t :: Strategy where
44+
ToTagsInstance (_ :+: _) = 'Custom
45+
ToTagsInstance Go.FunctionDeclaration = 'Custom
46+
ToTagsInstance Go.MethodDeclaration = 'Custom
47+
ToTagsInstance Go.CallExpression = 'Custom
48+
ToTagsInstance _ = 'Generic
49+
50+
instance ToTagsBy 'Custom Go.FunctionDeclaration where
51+
tags' t@Go.FunctionDeclaration
52+
{ ann = loc@Loc { byteRange }
53+
, name = Go.Identifier { text }
54+
} = yieldTag text Function loc byteRange >> gtags t
55+
56+
instance ToTagsBy 'Custom Go.MethodDeclaration where
57+
tags' t@Go.MethodDeclaration
58+
{ ann = loc@Loc { byteRange }
59+
, name = Go.FieldIdentifier { text }
60+
} = yieldTag text Function loc byteRange >> gtags t
61+
62+
instance ToTagsBy 'Custom Go.CallExpression where
63+
tags' t@Go.CallExpression
64+
{ ann = loc@Loc { byteRange }
65+
, function = Go.Expression expr
66+
} = match expr
67+
where
68+
match expr = case expr of
69+
Prj Go.SelectorExpression { field = Go.FieldIdentifier { text }} -> yield text
70+
Prj Go.Identifier { text } -> yield text
71+
Prj Go.CallExpression { function = Go.Expression e } -> match e
72+
_ -> gtags t
73+
yield name = yieldTag name Call loc byteRange >> gtags t
74+
75+
instance (ToTags l, ToTags r) => ToTagsBy 'Custom (l :+: r) where
76+
tags' (L1 l) = tags l
77+
tags' (R1 r) = tags r
78+
79+
gtags
80+
:: ( Has (Reader Source) sig m
81+
, Has (Writer Tags.Tags) sig m
82+
, Generic1 t
83+
, Tags.GFoldable1 ToTags (Rep1 t)
84+
)
85+
=> t Loc
86+
-> m ()
87+
gtags = getAp . Tags.gfoldMap1 @ToTags (Ap . tags) . from1
88+
89+
instance (Generic1 t, Tags.GFoldable1 ToTags (Rep1 t)) => ToTagsBy 'Generic t where
90+
tags' = gtags
91+
92+
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> Kind -> Loc -> Range -> m ()
93+
yieldTag name kind loc range = do
94+
src <- ask @Source
95+
let sliced = slice src range
96+
Tags.yield (Tag name kind loc (Tags.firstLine sliced) Nothing)

semantic.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -285,6 +285,7 @@ library
285285
, proto-lens-jsonpb
286286
, proto-lens-runtime >= 0.5 && <0.7
287287
, reducers ^>= 3.12.3
288+
, semantic-go ^>= 0
288289
, semantic-java ^>= 0
289290
, semantic-json ^>= 0
290291
, semantic-python ^>= 0

src/Data/Language.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -153,15 +153,15 @@ textToLanguage = \case
153153
data PerLanguageModes = PerLanguageModes
154154
{ pythonMode :: LanguageMode
155155
, rubyMode :: LanguageMode
156-
-- , typescriptMode :: LanguageMode
156+
, goMode :: LanguageMode
157157
}
158158
deriving (Eq, Ord, Show)
159159

160160
defaultLanguageModes :: PerLanguageModes
161161
defaultLanguageModes = PerLanguageModes
162162
{ pythonMode = ALaCarte
163163
, rubyMode = ALaCarte
164-
-- , typescriptMode = ALaCarte
164+
, goMode = ALaCarte
165165
}
166166

167167
data LanguageMode

src/Parsing/Parser.hs

Lines changed: 22 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,8 @@ module Parsing.Parser
55
-- $abstract
66
, SomeParser(..)
77
, goParser
8+
, goParserALaCarte
9+
, goParserPrecise
810
, javaParser
911
, javascriptParser
1012
, jsonParser
@@ -35,7 +37,8 @@ import qualified Data.Map as Map
3537
import qualified Data.Syntax as Syntax
3638
import Data.Term
3739
import Foreign.Ptr
38-
import qualified Language.Go.Assignment as Go
40+
import qualified Language.Go as GoPrecise
41+
import qualified Language.Go.Assignment as GoALaCarte
3942
import qualified Language.Java as Java
4043
import qualified Language.JSON as JSON
4144
import qualified Language.Markdown.Assignment as Markdown
@@ -103,8 +106,16 @@ data Parser term where
103106
data SomeParser c a where
104107
SomeParser :: c t => Parser (t a) -> SomeParser c a
105108

106-
goParser :: c Go.Term => (Language, SomeParser c Loc)
107-
goParser = (Go, SomeParser (AssignmentParser (ASTParser tree_sitter_go) Go.assignment))
109+
goParserALaCarte :: c GoALaCarte.Term => (Language, SomeParser c Loc)
110+
goParserALaCarte = (Go, SomeParser (AssignmentParser (ASTParser tree_sitter_go) GoALaCarte.assignment))
111+
112+
goParserPrecise :: c GoPrecise.Term => (Language, SomeParser c Loc)
113+
goParserPrecise = (Go, SomeParser (UnmarshalParser @GoPrecise.Term GoPrecise.tree_sitter_go))
114+
115+
goParser :: (c GoALaCarte.Term, c GoPrecise.Term) => PerLanguageModes -> (Language, SomeParser c Loc)
116+
goParser modes = case goMode modes of
117+
ALaCarte -> goParserALaCarte
118+
Precise -> goParserPrecise
108119

109120
javaParser :: c Java.Term => (Language, SomeParser c Loc)
110121
javaParser = (Java, SomeParser (UnmarshalParser @Java.Term Java.tree_sitter_java))
@@ -155,6 +166,7 @@ typescriptParser = (TypeScript, SomeParser (AssignmentParser (ASTParser tree_sit
155166

156167
-- | A type family selecting the language mode for a given term type.
157168
type family TermMode term where
169+
TermMode GoPrecise.Term = 'Precise
158170
TermMode Java.Term = 'Precise
159171
TermMode JSON.Term = 'Precise
160172
TermMode PythonPrecise.Term = 'Precise
@@ -164,7 +176,7 @@ type family TermMode term where
164176

165177
-- | The canonical set of parsers producing à la carte terms.
166178
aLaCarteParsers
167-
:: ( c Go.Term
179+
:: ( c GoALaCarte.Term
168180
, c Markdown.Term
169181
, c PHP.Term
170182
, c PythonALaCarte.Term
@@ -174,7 +186,7 @@ aLaCarteParsers
174186
)
175187
=> Map Language (SomeParser c Loc)
176188
aLaCarteParsers = Map.fromList
177-
[ goParser
189+
[ goParserALaCarte
178190
, javascriptParser
179191
, jsxParser
180192
, markdownParser
@@ -191,18 +203,21 @@ preciseParsers
191203
, c JSON.Term
192204
, c PythonPrecise.Term
193205
, c RubyPrecise.Term
206+
, c GoPrecise.Term
194207
)
195208
=> Map Language (SomeParser c Loc)
196209
preciseParsers = Map.fromList
197210
[ javaParser
198211
, jsonParser
199212
, pythonParserPrecise
200213
, rubyParserPrecise
214+
, goParserPrecise
201215
]
202216

203217
-- | The canonical set of all parsers for the passed per-language modes.
204218
allParsers
205-
:: ( c Go.Term
219+
:: ( c GoALaCarte.Term
220+
, c GoPrecise.Term
206221
, c Java.Term
207222
, c JSON.Term
208223
, c Markdown.Term
@@ -217,7 +232,7 @@ allParsers
217232
=> PerLanguageModes
218233
-> Map Language (SomeParser c Loc)
219234
allParsers modes = Map.fromList
220-
[ goParser
235+
[ goParser modes
221236
, javaParser
222237
, javascriptParser
223238
, jsonParser

src/Semantic/Api/Terms.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,7 @@ import Source.Loc
4040

4141
import qualified Language.Java as Java
4242
import qualified Language.JSON as JSON
43+
import qualified Language.Go as GoPrecise
4344
import qualified Language.Python as PythonPrecise
4445
import qualified Language.Ruby as RubyPrecise
4546

@@ -108,6 +109,9 @@ instance (TermMode term ~ strategy, ShowTermBy strategy term) => ShowTerm term w
108109
class ShowTermBy (strategy :: LanguageMode) term where
109110
showTermBy :: (Has (Reader Config) sig m) => term Loc -> m Builder
110111

112+
instance ShowTermBy 'Precise GoPrecise.Term where
113+
showTermBy = serialize Show . void . GoPrecise.getTerm
114+
111115
instance ShowTermBy 'Precise Java.Term where
112116
showTermBy = serialize Show . void . Java.getTerm
113117

@@ -136,6 +140,9 @@ instance (TermMode term ~ strategy, SExprTermBy strategy term) => SExprTerm term
136140
class SExprTermBy (strategy :: LanguageMode) term where
137141
sexprTermBy :: term Loc -> Builder
138142

143+
instance SExprTermBy 'Precise GoPrecise.Term where
144+
sexprTermBy = SExpr.Precise.serializeSExpression . GoPrecise.getTerm
145+
139146
instance SExprTermBy 'Precise Java.Term where
140147
sexprTermBy = SExpr.Precise.serializeSExpression . Java.getTerm
141148

src/Semantic/CLI.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -178,6 +178,11 @@ languageModes = Language.PerLanguageModes
178178
<> metavar "ALaCarte|Precise"
179179
<> value Language.ALaCarte
180180
<> showDefault)
181+
<*> option auto ( long "go-mode"
182+
<> help "The AST representation to use for Go sources"
183+
<> metavar "ALaCarte|Precise"
184+
<> value Language.ALaCarte
185+
<> showDefault)
181186

182187
filePathReader :: ReadM File
183188
filePathReader = fileForPath <$> str

src/Semantic/Graph.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -104,7 +104,7 @@ instance
104104

105105
analysisParsers :: Map Language (SomeParser AnalyzeTerm Loc)
106106
analysisParsers = Map.fromList
107-
[ goParser
107+
[ goParserALaCarte
108108
, javascriptParser
109109
, phpParser
110110
, pythonParserALaCarte

0 commit comments

Comments
 (0)