mirror of
https://github.com/github/semantic.git
synced 2024-11-23 08:27:56 +03:00
Move the rest of the languages over to generated datatypes
This commit is contained in:
parent
1de1ba7fe3
commit
38a7158b20
@ -18,9 +18,9 @@ import Control.Effect.Writer
|
||||
import Data.Foldable (for_)
|
||||
import Data.Text (Text)
|
||||
import qualified Language.CodeQL.AST as CodeQL
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Source as Source
|
||||
import Proto.Semantic as P
|
||||
import Tags.Tag
|
||||
import qualified Tags.Tagging.Precise as Tags
|
||||
|
||||
|
@ -26,6 +26,7 @@ common haskell
|
||||
, parsers ^>= 0.12.10
|
||||
, semantic-ast
|
||||
, semantic-core ^>= 0.0
|
||||
, semantic-proto ^>= 0
|
||||
, semantic-source ^>= 0.1.0
|
||||
, semantic-tags ^>= 0.0
|
||||
, template-haskell ^>= 2.15
|
||||
|
@ -16,6 +16,7 @@ import Control.Effect.Reader
|
||||
import Control.Effect.Writer
|
||||
import Data.Text as Text
|
||||
import qualified Language.Go.AST as Go
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Source as Source
|
||||
import Tags.Tag
|
||||
@ -42,14 +43,14 @@ instance ToTags Go.FunctionDeclaration where
|
||||
t@Go.FunctionDeclaration
|
||||
{ ann = Loc {byteRange},
|
||||
name = Go.Identifier {text, ann}
|
||||
} = yieldTag text Function ann byteRange >> gtags t
|
||||
} = yieldTag text P.FUNCTION ann byteRange >> gtags t
|
||||
|
||||
instance ToTags Go.MethodDeclaration where
|
||||
tags
|
||||
t@Go.MethodDeclaration
|
||||
{ ann = Loc {byteRange},
|
||||
name = Go.FieldIdentifier {text, ann}
|
||||
} = yieldTag text Method ann byteRange >> gtags t
|
||||
} = yieldTag text P.METHOD ann byteRange >> gtags t
|
||||
|
||||
instance ToTags Go.CallExpression where
|
||||
tags
|
||||
@ -64,7 +65,7 @@ instance ToTags Go.CallExpression where
|
||||
Prj Go.CallExpression {function = Go.Expression e} -> match e
|
||||
Prj Go.ParenthesizedExpression {extraChildren = Go.Expression e} -> match e
|
||||
_ -> gtags t
|
||||
yield name loc = yieldTag name Call loc byteRange >> gtags t
|
||||
yield name loc = yieldTag name P.CALL loc byteRange >> gtags t
|
||||
|
||||
instance (ToTags l, ToTags r) => ToTags (l :+: r) where
|
||||
tags (L1 l) = tags l
|
||||
@ -81,7 +82,7 @@ gtags ::
|
||||
m ()
|
||||
gtags = traverse1_ @ToTags (const (pure ())) tags
|
||||
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> Kind -> Loc -> Range -> m ()
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> P.SyntaxType -> Loc -> Range -> m ()
|
||||
yieldTag name kind loc srcLineRange = do
|
||||
src <- ask @Source
|
||||
Tags.yield (Tag name kind loc (Tags.firstLine src srcLineRange) Nothing)
|
||||
|
@ -26,6 +26,7 @@ common haskell
|
||||
, parsers ^>= 0.12.10
|
||||
, semantic-ast
|
||||
, semantic-core ^>= 0.0
|
||||
, semantic-proto ^>= 0
|
||||
, semantic-source ^>= 0.1.0
|
||||
, semantic-tags ^>= 0.0
|
||||
, template-haskell ^>= 2.15
|
||||
|
@ -17,6 +17,7 @@ import Control.Effect.Reader
|
||||
import Control.Effect.Writer
|
||||
import Data.Foldable
|
||||
import qualified Language.Java.AST as Java
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Range
|
||||
import Source.Source as Source
|
||||
@ -61,7 +62,7 @@ instance ToTags Java.MethodDeclaration where
|
||||
Just Java.Block {ann = Loc Range {end} _} -> end
|
||||
Nothing -> end range
|
||||
}
|
||||
Tags.yield (Tag text Method ann line Nothing)
|
||||
Tags.yield (Tag text P.METHOD ann line Nothing)
|
||||
gtags t
|
||||
|
||||
-- TODO: we can coalesce a lot of these instances given proper use of HasField
|
||||
@ -75,7 +76,7 @@ instance ToTags Java.ClassDeclaration where
|
||||
body = Java.ClassBody {ann = Loc Range {start = end} _}
|
||||
} = do
|
||||
src <- ask @Source
|
||||
Tags.yield (Tag text Class ann (Tags.firstLine src (Range start end)) Nothing)
|
||||
Tags.yield (Tag text P.CLASS ann (Tags.firstLine src (Range start end)) Nothing)
|
||||
gtags t
|
||||
|
||||
instance ToTags Java.MethodInvocation where
|
||||
@ -85,7 +86,7 @@ instance ToTags Java.MethodInvocation where
|
||||
name = Java.Identifier {text, ann}
|
||||
} = do
|
||||
src <- ask @Source
|
||||
Tags.yield (Tag text Call ann (Tags.firstLine src range) Nothing)
|
||||
Tags.yield (Tag text P.CALL ann (Tags.firstLine src range) Nothing)
|
||||
gtags t
|
||||
|
||||
instance ToTags Java.InterfaceDeclaration where
|
||||
@ -95,7 +96,7 @@ instance ToTags Java.InterfaceDeclaration where
|
||||
name = Java.Identifier {text, ann}
|
||||
} = do
|
||||
src <- ask @Source
|
||||
Tags.yield (Tag text Interface ann (Tags.firstLine src byteRange) Nothing)
|
||||
Tags.yield (Tag text P.INTERFACE ann (Tags.firstLine src byteRange) Nothing)
|
||||
gtags t
|
||||
|
||||
instance ToTags Java.InterfaceTypeList where
|
||||
@ -103,7 +104,7 @@ instance ToTags Java.InterfaceTypeList where
|
||||
src <- ask @Source
|
||||
for_ interfaces $ \x -> case x of
|
||||
Java.Type (Prj (Java.UnannotatedType (Prj (Java.SimpleType (Prj Java.TypeIdentifier {ann = loc@Loc {byteRange = range}, text = name}))))) ->
|
||||
Tags.yield (Tag name Implementation loc (Tags.firstLine src range) Nothing)
|
||||
Tags.yield (Tag name P.IMPLEMENTATION loc (Tags.firstLine src range) Nothing)
|
||||
_ -> pure ()
|
||||
gtags t
|
||||
|
||||
|
@ -25,6 +25,7 @@ common haskell
|
||||
, fused-syntax
|
||||
, parsers ^>= 0.12.10
|
||||
, semantic-ast
|
||||
, semantic-proto ^>= 0
|
||||
, semantic-core ^>= 0.0
|
||||
, semantic-source ^>= 0.1.0
|
||||
, semantic-tags ^>= 0.0
|
||||
|
@ -18,6 +18,7 @@ import Control.Effect.Reader
|
||||
import Control.Effect.Writer
|
||||
import Data.Text (Text)
|
||||
import qualified Language.PHP.AST as PHP
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Source as Source
|
||||
import Tags.Tag
|
||||
@ -54,7 +55,7 @@ gtags ::
|
||||
m ()
|
||||
gtags = traverse1_ @ToTags (const (pure ())) tags
|
||||
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> Kind -> Loc -> Range -> m ()
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> P.SyntaxType -> Loc -> Range -> m ()
|
||||
yieldTag name kind loc srcLineRange = do
|
||||
src <- ask @Source
|
||||
Tags.yield (Tag name kind loc (Tags.firstLine src srcLineRange) Nothing)
|
||||
@ -64,14 +65,14 @@ instance ToTags PHP.FunctionDefinition where
|
||||
t@PHP.FunctionDefinition
|
||||
{ PHP.ann = Loc {byteRange},
|
||||
PHP.name = PHP.Name {text, ann}
|
||||
} = yieldTag text Method ann byteRange >> gtags t
|
||||
} = yieldTag text P.METHOD ann byteRange >> gtags t
|
||||
|
||||
instance ToTags PHP.MethodDeclaration where
|
||||
tags
|
||||
t@PHP.MethodDeclaration
|
||||
{ PHP.ann = Loc {byteRange},
|
||||
PHP.name = PHP.Name {text, ann}
|
||||
} = yieldTag text Function ann byteRange >> gtags t
|
||||
} = yieldTag text P.FUNCTION ann byteRange >> gtags t
|
||||
|
||||
instance ToTags PHP.FunctionCallExpression where
|
||||
tags
|
||||
@ -80,7 +81,7 @@ instance ToTags PHP.FunctionCallExpression where
|
||||
PHP.function = func
|
||||
} = match func
|
||||
where
|
||||
yield name loc = yieldTag name Call loc byteRange >> gtags t
|
||||
yield name loc = yieldTag name P.CALL loc byteRange >> gtags t
|
||||
match expr = case expr of
|
||||
Prj PHP.VariableName {extraChildren = PHP.Name {text, ann}} -> yield text ann *> gtags t
|
||||
Prj PHP.QualifiedName {extraChildren = [Prj PHP.Name {text, ann}]} -> yield text ann *> gtags t
|
||||
@ -92,7 +93,7 @@ instance ToTags PHP.MemberCallExpression where
|
||||
t@PHP.MemberCallExpression
|
||||
{ PHP.ann = Loc {byteRange},
|
||||
PHP.name = Prj PHP.Name {text, ann}
|
||||
} = yieldTag text Call ann byteRange >> gtags t
|
||||
} = yieldTag text P.CALL ann byteRange >> gtags t
|
||||
tags t = gtags t
|
||||
|
||||
|
||||
|
@ -27,6 +27,7 @@ common haskell
|
||||
, semantic-analysis ^>= 0
|
||||
, semantic-ast
|
||||
, semantic-core ^>= 0.0
|
||||
, semantic-proto ^>= 0
|
||||
, semantic-source ^>= 0.1.0
|
||||
, semantic-tags ^>= 0.0
|
||||
, semantic-scope-graph ^>= 0.0
|
||||
|
@ -21,6 +21,7 @@ import Data.List.NonEmpty (NonEmpty (..))
|
||||
import Data.Maybe (listToMaybe)
|
||||
import Data.Text as Text
|
||||
import qualified Language.Python.AST as Py
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Range
|
||||
import Source.Source as Source
|
||||
@ -59,7 +60,7 @@ keywordFunctionCall ::
|
||||
Range ->
|
||||
Text ->
|
||||
m ()
|
||||
keywordFunctionCall t loc range name = yieldTag name Function loc range Nothing >> gtags t
|
||||
keywordFunctionCall t loc range name = yieldTag name P.FUNCTION loc range Nothing >> gtags t
|
||||
|
||||
instance ToTags Py.String where
|
||||
tags Py.String {extraChildren} = for_ extraChildren $ \x -> case x of
|
||||
@ -101,7 +102,7 @@ instance ToTags Py.FunctionDefinition where
|
||||
} = do
|
||||
src <- ask @Source
|
||||
let docs = listToMaybe extraChildren >>= docComment src
|
||||
yieldTag text Function ann (Range start end) docs >> gtags t
|
||||
yieldTag text P.FUNCTION ann (Range start end) docs >> gtags t
|
||||
|
||||
instance ToTags Py.ClassDefinition where
|
||||
tags
|
||||
@ -112,7 +113,7 @@ instance ToTags Py.ClassDefinition where
|
||||
} = do
|
||||
src <- ask @Source
|
||||
let docs = listToMaybe extraChildren >>= docComment src
|
||||
yieldTag text Class ann (Range start end) docs >> gtags t
|
||||
yieldTag text P.CLASS ann (Range start end) docs >> gtags t
|
||||
|
||||
instance ToTags Py.Call where
|
||||
tags
|
||||
@ -127,9 +128,9 @@ instance ToTags Py.Call where
|
||||
Prj Py.Call {function = Py.PrimaryExpression expr'} -> match expr' -- Nested call expression like this in Python represent creating an instance of a class and calling it: e.g. AClass()()
|
||||
Prj (Py.ParenthesizedExpression _ (Prj (Py.Expression (Prj (Py.PrimaryExpression expr'))))) -> match expr' -- Parenthesized expressions
|
||||
_ -> gtags t
|
||||
yield name loc = yieldTag name Call loc byteRange Nothing >> gtags t
|
||||
yield name loc = yieldTag name P.CALL loc byteRange Nothing >> gtags t
|
||||
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> Kind -> Loc -> Range -> Maybe Text -> m ()
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> P.SyntaxType -> Loc -> Range -> Maybe Text -> m ()
|
||||
yieldTag name kind loc srcLineRange docs = do
|
||||
src <- ask @Source
|
||||
Tags.yield (Tag name kind loc (Tags.firstLine src srcLineRange) docs)
|
||||
|
@ -26,6 +26,7 @@ common haskell
|
||||
, parsers ^>= 0.12.10
|
||||
, semantic-ast
|
||||
, semantic-core ^>= 0.0
|
||||
, semantic-proto ^>= 0
|
||||
, semantic-source ^>= 0.1.0
|
||||
, semantic-tags ^>= 0.0
|
||||
, template-haskell ^>= 2.15
|
||||
|
@ -25,6 +25,7 @@ import Control.Monad
|
||||
import Data.Foldable
|
||||
import Data.Text as Text
|
||||
import qualified Language.Ruby.AST as Rb
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Range as Range
|
||||
import Source.Source as Source
|
||||
@ -72,8 +73,8 @@ nameBlacklist =
|
||||
"lambda"
|
||||
]
|
||||
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> Kind -> Loc -> Range -> m ()
|
||||
yieldTag name Call _ _ | name `elem` nameBlacklist = pure ()
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> P.SyntaxType -> Loc -> Range -> m ()
|
||||
yieldTag name P.CALL _ _ | name `elem` nameBlacklist = pure ()
|
||||
yieldTag name kind loc srcLineRange = do
|
||||
src <- ask @Source
|
||||
Tags.yield (Tag name kind loc (Tags.firstLine src srcLineRange) Nothing)
|
||||
@ -94,7 +95,7 @@ instance ToTags Rb.Class where
|
||||
Prj Rb.Superclass {ann = Loc {byteRange = Range {end}}} : _ -> Range start end
|
||||
_ -> Range start (getEnd expr)
|
||||
getEnd = Range.end . byteRange . TS.gann
|
||||
yield name loc = yieldTag name Class loc range' >> gtags t
|
||||
yield name loc = yieldTag name P.CLASS loc range' >> gtags t
|
||||
|
||||
instance ToTags Rb.SingletonClass where
|
||||
tags
|
||||
@ -112,7 +113,7 @@ instance ToTags Rb.SingletonClass where
|
||||
x : _ -> Range start (getStart x)
|
||||
_ -> range
|
||||
getStart = Range.start . byteRange . TS.gann
|
||||
yield name loc = yieldTag name Class loc range' >> gtags t
|
||||
yield name loc = yieldTag name P.CLASS loc range' >> gtags t
|
||||
|
||||
instance ToTags Rb.Module where
|
||||
tags
|
||||
@ -131,7 +132,7 @@ instance ToTags Rb.Module where
|
||||
_ -> Range start (getEnd expr)
|
||||
getEnd = Range.end . byteRange . TS.gann
|
||||
getStart = Range.start . byteRange . TS.gann
|
||||
yield name loc = yieldTag name Module loc range' >> gtags t
|
||||
yield name loc = yieldTag name P.MODULE loc range' >> gtags t
|
||||
|
||||
yieldMethodNameTag ::
|
||||
( Has (State [Text]) sig m,
|
||||
@ -155,7 +156,7 @@ yieldMethodNameTag t range (Rb.MethodName expr) = enterScope True $ case expr of
|
||||
-- Prj Rb.Symbol { extraChildren = [Prj Rb.EscapeSequence { text = name }] } -> yield name
|
||||
_ -> gtags t
|
||||
where
|
||||
yield name loc = yieldTag name Method loc range >> gtags t
|
||||
yield name loc = yieldTag name P.METHOD loc range >> gtags t
|
||||
|
||||
enterScope :: (Has (State [Text]) sig m) => Bool -> m () -> m ()
|
||||
enterScope createNew m = do
|
||||
@ -241,13 +242,13 @@ instance ToTags Rb.Lhs where
|
||||
Prj Rb.Operator {text, ann} -> yieldCall text ann byteRange
|
||||
_ -> gtags t
|
||||
-- These do check for locals before yielding a call tag
|
||||
Prj (Rb.Variable (Prj Rb.Identifier {ann = loc@Loc {byteRange}, text})) -> yield text Call loc byteRange
|
||||
Prj Rb.ScopeResolution {ann = loc@Loc {byteRange}, name = Prj Rb.Identifier {text}} -> yield text Call loc byteRange
|
||||
Prj (Rb.Variable (Prj Rb.Constant { ann = loc@Loc { byteRange }, text })) -> yield text Call loc byteRange -- TODO: Should yield Constant
|
||||
Prj Rb.ScopeResolution { ann = loc@Loc { byteRange }, name = Prj Rb.Constant { text } } -> yield text Call loc byteRange -- TODO: Should yield Constant
|
||||
Prj (Rb.Variable (Prj Rb.Identifier {ann = loc@Loc {byteRange}, text})) -> yield text P.CALL loc byteRange
|
||||
Prj Rb.ScopeResolution {ann = loc@Loc {byteRange}, name = Prj Rb.Identifier {text}} -> yield text P.CALL loc byteRange
|
||||
Prj (Rb.Variable (Prj Rb.Constant { ann = loc@Loc { byteRange }, text })) -> yield text P.CALL loc byteRange -- TODO: Should yield Constant
|
||||
Prj Rb.ScopeResolution { ann = loc@Loc { byteRange }, name = Prj Rb.Constant { text } } -> yield text P.CALL loc byteRange -- TODO: Should yield Constant
|
||||
_ -> gtags t
|
||||
where
|
||||
yieldCall name loc range = yieldTag name Call loc range >> gtags t
|
||||
yieldCall name loc range = yieldTag name P.CALL loc range >> gtags t
|
||||
yield name kind loc range = do
|
||||
locals <- get @[Text]
|
||||
unless (name `elem` locals) $ yieldTag name kind loc range
|
||||
@ -260,14 +261,14 @@ instance ToTags Rb.MethodCall where
|
||||
{ ann = Loc {byteRange = byteRange@Range {}},
|
||||
method = expr
|
||||
} = case expr of
|
||||
Prj (Rb.Variable (Prj Rb.Identifier {text, ann})) -> yield text Call ann
|
||||
Prj (Rb.Variable (Prj Rb.Constant {text, ann})) -> yield text Call ann -- TODO: Should yield Constant
|
||||
Prj Rb.ScopeResolution {name = Prj Rb.Identifier {text, ann}} -> yield text Call ann
|
||||
Prj Rb.ScopeResolution {name = Prj Rb.Constant {text, ann}} -> yield text Call ann -- TODO: Should yield Constant
|
||||
Prj (Rb.Variable (Prj Rb.Identifier {text, ann})) -> yield text P.CALL ann
|
||||
Prj (Rb.Variable (Prj Rb.Constant {text, ann})) -> yield text P.CALL ann -- TODO: Should yield Constant
|
||||
Prj Rb.ScopeResolution {name = Prj Rb.Identifier {text, ann}} -> yield text P.CALL ann
|
||||
Prj Rb.ScopeResolution {name = Prj Rb.Constant {text, ann}} -> yield text P.CALL ann -- TODO: Should yield Constant
|
||||
Prj Rb.Call {method} -> case method of
|
||||
Prj Rb.Identifier {text, ann} -> yield text Call ann
|
||||
Prj Rb.Constant {text, ann} -> yield text Call ann
|
||||
Prj Rb.Operator {text, ann} -> yield text Call ann
|
||||
Prj Rb.Identifier {text, ann} -> yield text P.CALL ann
|
||||
Prj Rb.Constant {text, ann} -> yield text P.CALL ann
|
||||
Prj Rb.Operator {text, ann} -> yield text P.CALL ann
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
where
|
||||
@ -281,10 +282,10 @@ instance ToTags Rb.Alias where
|
||||
ann = Loc {byteRange}
|
||||
} = do
|
||||
case aliasExpr of
|
||||
Prj Rb.Identifier {ann, text} -> yieldTag text Function ann byteRange
|
||||
Prj Rb.Identifier {ann, text} -> yieldTag text P.FUNCTION ann byteRange
|
||||
_ -> tags aliasExpr
|
||||
case nameExpr of
|
||||
Prj Rb.Identifier {ann, text} -> yieldTag text Call ann byteRange
|
||||
Prj Rb.Identifier {ann, text} -> yieldTag text P.CALL ann byteRange
|
||||
_ -> tags nameExpr
|
||||
gtags t
|
||||
|
||||
@ -295,7 +296,7 @@ instance ToTags Rb.Undef where
|
||||
ann = Loc {byteRange}
|
||||
} = for_ extraChildren $ \(Rb.MethodName expr) -> do
|
||||
case expr of
|
||||
Prj Rb.Identifier {ann, text} -> yieldTag text Call ann byteRange
|
||||
Prj Rb.Identifier {ann, text} -> yieldTag text P.CALL ann byteRange
|
||||
_ -> tags expr
|
||||
gtags t
|
||||
|
||||
|
@ -26,6 +26,7 @@ common haskell
|
||||
, parsers ^>= 0.12.10
|
||||
, semantic-ast
|
||||
, semantic-core ^>= 0.0
|
||||
, semantic-proto ^>= 0
|
||||
, semantic-source ^>= 0.1.0
|
||||
, semantic-tags ^>= 0.0
|
||||
, template-haskell ^>= 2.15
|
||||
@ -84,4 +85,4 @@ test-suite test
|
||||
-Wno-all-missed-specialisations
|
||||
-Wno-star-is-type
|
||||
if (impl(ghc >= 8.8))
|
||||
ghc-options: -Wno-missing-deriving-strategies
|
||||
ghc-options: -Wno-missing-deriving-strategies
|
||||
|
@ -205,4 +205,4 @@ instance ToTags Rust.VisibilityModifier
|
||||
instance ToTags Rust.WhereClause
|
||||
instance ToTags Rust.WherePredicate
|
||||
instance ToTags Rust.WhileExpression
|
||||
instance ToTags Rust.WhileLetExpression
|
||||
instance ToTags Rust.WhileLetExpression
|
||||
|
@ -26,6 +26,7 @@ common haskell
|
||||
, parsers ^>= 0.12.10
|
||||
, semantic-ast
|
||||
, semantic-core ^>= 0.0
|
||||
, semantic-proto ^>= 0
|
||||
, semantic-source ^>= 0.1.0
|
||||
, semantic-tags ^>= 0.0
|
||||
, template-haskell ^>= 2.15
|
||||
|
@ -19,6 +19,7 @@ import Control.Effect.Writer
|
||||
import Data.Foldable
|
||||
import Data.Text as Text
|
||||
import qualified Language.TSX.AST as Tsx
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Source as Source
|
||||
import Tags.Tag
|
||||
@ -42,20 +43,20 @@ class ToTags t where
|
||||
|
||||
instance ToTags Tsx.Function where
|
||||
tags t@Tsx.Function {ann = Loc {byteRange}, name = Just Tsx.Identifier {text, ann}} =
|
||||
yieldTag text Function ann byteRange >> gtags t
|
||||
yieldTag text P.FUNCTION ann byteRange >> gtags t
|
||||
tags t = gtags t
|
||||
|
||||
instance ToTags Tsx.FunctionSignature where
|
||||
tags t@Tsx.FunctionSignature {ann = Loc {byteRange}, name = Tsx.Identifier {text, ann}} =
|
||||
yieldTag text Function ann byteRange >> gtags t
|
||||
yieldTag text P.FUNCTION ann byteRange >> gtags t
|
||||
|
||||
instance ToTags Tsx.FunctionDeclaration where
|
||||
tags t@Tsx.FunctionDeclaration {ann = Loc {byteRange}, name = Tsx.Identifier {text, ann}} =
|
||||
yieldTag text Function ann byteRange >> gtags t
|
||||
yieldTag text P.FUNCTION ann byteRange >> gtags t
|
||||
|
||||
instance ToTags Tsx.MethodDefinition where
|
||||
tags t@Tsx.MethodDefinition {ann = Loc {byteRange}, name} = case name of
|
||||
Prj Tsx.PropertyIdentifier {text, ann} -> yieldTag text Method ann byteRange >> gtags t
|
||||
Prj Tsx.PropertyIdentifier {text, ann} -> yieldTag text P.METHOD ann byteRange >> gtags t
|
||||
_ -> gtags t
|
||||
|
||||
instance ToTags Tsx.Pair where
|
||||
@ -64,11 +65,11 @@ instance ToTags Tsx.Pair where
|
||||
(Prj Tsx.PropertyIdentifier {text, ann}, Prj Tsx.ArrowFunction {}) -> yield text ann
|
||||
_ -> gtags t
|
||||
where
|
||||
yield text loc = yieldTag text Function loc byteRange >> gtags t
|
||||
yield text loc = yieldTag text P.FUNCTION loc byteRange >> gtags t
|
||||
|
||||
instance ToTags Tsx.ClassDeclaration where
|
||||
tags t@Tsx.ClassDeclaration {ann = Loc {byteRange}, name = Tsx.TypeIdentifier {text, ann}} =
|
||||
yieldTag text Class ann byteRange >> gtags t
|
||||
yieldTag text P.CLASS ann byteRange >> gtags t
|
||||
|
||||
instance ToTags Tsx.CallExpression where
|
||||
tags t@Tsx.CallExpression {ann = Loc {byteRange}, function = Tsx.Expression expr} = match expr
|
||||
@ -83,16 +84,16 @@ instance ToTags Tsx.CallExpression where
|
||||
Prj (Tsx.Expression expr) -> match expr
|
||||
_ -> tags x
|
||||
_ -> gtags t
|
||||
yield name loc = yieldTag name Call loc byteRange >> gtags t
|
||||
yield name loc = yieldTag name P.CALL loc byteRange >> gtags t
|
||||
|
||||
instance ToTags Tsx.Class where
|
||||
tags t@Tsx.Class {ann = Loc {byteRange}, name = Just Tsx.TypeIdentifier {text, ann}} =
|
||||
yieldTag text Class ann byteRange >> gtags t
|
||||
yieldTag text P.CLASS ann byteRange >> gtags t
|
||||
tags t = gtags t
|
||||
|
||||
instance ToTags Tsx.Module where
|
||||
tags t@Tsx.Module {ann = Loc {byteRange}, name} = case name of
|
||||
Prj Tsx.Identifier {text, ann} -> yieldTag text Module ann byteRange >> gtags t
|
||||
Prj Tsx.Identifier {text, ann} -> yieldTag text P.MODULE ann byteRange >> gtags t
|
||||
_ -> gtags t
|
||||
|
||||
instance ToTags Tsx.VariableDeclarator where
|
||||
@ -102,7 +103,7 @@ instance ToTags Tsx.VariableDeclarator where
|
||||
(Prj Tsx.ArrowFunction {}, Prj Tsx.Identifier {text, ann}) -> yield text ann
|
||||
_ -> gtags t
|
||||
where
|
||||
yield text loc = yieldTag text Function loc byteRange >> gtags t
|
||||
yield text loc = yieldTag text P.FUNCTION loc byteRange >> gtags t
|
||||
tags t = gtags t
|
||||
|
||||
instance ToTags Tsx.AssignmentExpression where
|
||||
@ -114,7 +115,7 @@ instance ToTags Tsx.AssignmentExpression where
|
||||
(Prj Tsx.MemberExpression {property = Tsx.PropertyIdentifier {text, ann}}, Prj Tsx.ArrowFunction {}) -> yield text ann
|
||||
_ -> gtags t
|
||||
where
|
||||
yield text loc = yieldTag text Function loc byteRange >> gtags t
|
||||
yield text loc = yieldTag text P.FUNCTION loc byteRange >> gtags t
|
||||
|
||||
instance (ToTags l, ToTags r) => ToTags (l :+: r) where
|
||||
tags (L1 l) = tags l
|
||||
@ -137,8 +138,8 @@ gtags = traverse1_ @ToTags (const (pure ())) tags
|
||||
nameBlacklist :: [Text]
|
||||
nameBlacklist = ["require"]
|
||||
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> Kind -> Loc -> Range -> m ()
|
||||
yieldTag name Call _ _ | name `elem` nameBlacklist = pure ()
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> P.SyntaxType -> Loc -> Range -> m ()
|
||||
yieldTag name P.CALL _ _ | name `elem` nameBlacklist = pure ()
|
||||
yieldTag name kind loc srcLineRange = do
|
||||
src <- ask @Source
|
||||
Tags.yield (Tag name kind loc (Tags.firstLine src srcLineRange) Nothing)
|
||||
|
@ -26,6 +26,7 @@ common haskell
|
||||
, parsers ^>= 0.12.10
|
||||
, semantic-ast
|
||||
, semantic-core ^>= 0.0
|
||||
, semantic-proto ^>= 0
|
||||
, semantic-source ^>= 0.1.0
|
||||
, semantic-tags ^>= 0.0
|
||||
, template-haskell ^>= 2.15
|
||||
|
@ -19,6 +19,7 @@ import Control.Effect.Writer
|
||||
import Data.Foldable
|
||||
import Data.Text as Text
|
||||
import qualified Language.TypeScript.AST as Ts
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Source as Source
|
||||
import Tags.Tag
|
||||
@ -42,20 +43,20 @@ class ToTags t where
|
||||
|
||||
instance ToTags Ts.Function where
|
||||
tags t@Ts.Function {ann = Loc {byteRange}, name = Just Ts.Identifier {text, ann}} =
|
||||
yieldTag text Function ann byteRange >> gtags t
|
||||
yieldTag text P.FUNCTION ann byteRange >> gtags t
|
||||
tags t = gtags t
|
||||
|
||||
instance ToTags Ts.FunctionSignature where
|
||||
tags t@Ts.FunctionSignature {ann = Loc {byteRange}, name = Ts.Identifier {text, ann}} =
|
||||
yieldTag text Function ann byteRange >> gtags t
|
||||
yieldTag text P.FUNCTION ann byteRange >> gtags t
|
||||
|
||||
instance ToTags Ts.FunctionDeclaration where
|
||||
tags t@Ts.FunctionDeclaration {ann = Loc {byteRange}, name = Ts.Identifier {text, ann}} =
|
||||
yieldTag text Function ann byteRange >> gtags t
|
||||
yieldTag text P.FUNCTION ann byteRange >> gtags t
|
||||
|
||||
instance ToTags Ts.MethodDefinition where
|
||||
tags t@Ts.MethodDefinition {ann = Loc {byteRange}, name} = case name of
|
||||
Prj Ts.PropertyIdentifier {text, ann} -> yieldTag text Method ann byteRange >> gtags t
|
||||
Prj Ts.PropertyIdentifier {text, ann} -> yieldTag text P.METHOD ann byteRange >> gtags t
|
||||
_ -> gtags t
|
||||
|
||||
instance ToTags Ts.Pair where
|
||||
@ -64,11 +65,11 @@ instance ToTags Ts.Pair where
|
||||
(Prj Ts.PropertyIdentifier {text, ann}, Prj Ts.ArrowFunction {}) -> yield text ann
|
||||
_ -> gtags t
|
||||
where
|
||||
yield text loc = yieldTag text Function loc byteRange >> gtags t
|
||||
yield text loc = yieldTag text P.FUNCTION loc byteRange >> gtags t
|
||||
|
||||
instance ToTags Ts.ClassDeclaration where
|
||||
tags t@Ts.ClassDeclaration {ann = Loc {byteRange}, name = Ts.TypeIdentifier {text, ann}} =
|
||||
yieldTag text Class ann byteRange >> gtags t
|
||||
yieldTag text P.CLASS ann byteRange >> gtags t
|
||||
|
||||
instance ToTags Ts.CallExpression where
|
||||
tags t@Ts.CallExpression {ann = Loc {byteRange}, function = Ts.Expression expr} = match expr
|
||||
@ -83,16 +84,16 @@ instance ToTags Ts.CallExpression where
|
||||
Prj (Ts.Expression expr) -> match expr
|
||||
_ -> tags x
|
||||
_ -> gtags t
|
||||
yield name loc = yieldTag name Call loc byteRange >> gtags t
|
||||
yield name loc = yieldTag name P.CALL loc byteRange >> gtags t
|
||||
|
||||
instance ToTags Ts.Class where
|
||||
tags t@Ts.Class {ann = Loc {byteRange}, name = Just Ts.TypeIdentifier {text, ann}} =
|
||||
yieldTag text Class ann byteRange >> gtags t
|
||||
yieldTag text P.CLASS ann byteRange >> gtags t
|
||||
tags t = gtags t
|
||||
|
||||
instance ToTags Ts.Module where
|
||||
tags t@Ts.Module {ann = Loc {byteRange}, name} = case name of
|
||||
Prj Ts.Identifier {text, ann} -> yieldTag text Module ann byteRange >> gtags t
|
||||
Prj Ts.Identifier {text, ann} -> yieldTag text P.MODULE ann byteRange >> gtags t
|
||||
_ -> gtags t
|
||||
|
||||
instance ToTags Ts.VariableDeclarator where
|
||||
@ -102,7 +103,7 @@ instance ToTags Ts.VariableDeclarator where
|
||||
(Prj Ts.ArrowFunction {}, Prj Ts.Identifier {text, ann}) -> yield text ann
|
||||
_ -> gtags t
|
||||
where
|
||||
yield text loc = yieldTag text Function loc byteRange >> gtags t
|
||||
yield text loc = yieldTag text P.FUNCTION loc byteRange >> gtags t
|
||||
tags t = gtags t
|
||||
|
||||
instance ToTags Ts.AssignmentExpression where
|
||||
@ -114,7 +115,7 @@ instance ToTags Ts.AssignmentExpression where
|
||||
(Prj Ts.MemberExpression {property = Ts.PropertyIdentifier {text, ann}}, Prj Ts.ArrowFunction {}) -> yield text ann
|
||||
_ -> gtags t
|
||||
where
|
||||
yield text loc = yieldTag text Function loc byteRange >> gtags t
|
||||
yield text loc = yieldTag text P.FUNCTION loc byteRange >> gtags t
|
||||
|
||||
instance (ToTags l, ToTags r) => ToTags (l :+: r) where
|
||||
tags (L1 l) = tags l
|
||||
@ -137,8 +138,8 @@ gtags = traverse1_ @ToTags (const (pure ())) tags
|
||||
nameBlacklist :: [Text]
|
||||
nameBlacklist = ["require"]
|
||||
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> Kind -> Loc -> Range -> m ()
|
||||
yieldTag name Call _ _ | name `elem` nameBlacklist = pure ()
|
||||
yieldTag :: (Has (Reader Source) sig m, Has (Writer Tags.Tags) sig m) => Text -> P.SyntaxType -> Loc -> Range -> m ()
|
||||
yieldTag name P.CALL _ _ | name `elem` nameBlacklist = pure ()
|
||||
yieldTag name kind loc srcLineRange = do
|
||||
src <- ask @Source
|
||||
Tags.yield (Tag name kind loc (Tags.firstLine src srcLineRange) Nothing)
|
||||
|
Loading…
Reference in New Issue
Block a user