mirror of
https://github.com/github/semantic.git
synced 2024-11-23 08:27:56 +03:00
Hide a symbol.
This commit is contained in:
parent
2a92d1fa71
commit
b7653156a4
@ -13,22 +13,22 @@ module Language.Ruby.Tags
|
||||
)
|
||||
where
|
||||
|
||||
import AST.Element
|
||||
import AST.Element
|
||||
import qualified AST.Parse as Parse
|
||||
import AST.Token
|
||||
import AST.Traversable1
|
||||
import AST.Token
|
||||
import AST.Traversable1
|
||||
import qualified AST.Unmarshal as TS
|
||||
import Control.Effect.Reader
|
||||
import Control.Effect.State
|
||||
import Control.Effect.Writer
|
||||
import Control.Monad
|
||||
import Data.Foldable
|
||||
import Data.Text as Text
|
||||
import Control.Effect.Reader
|
||||
import Control.Effect.State
|
||||
import Control.Effect.Writer
|
||||
import Control.Monad
|
||||
import Data.Foldable
|
||||
import Data.Text as Text hiding (elem)
|
||||
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
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Range as Range
|
||||
import Source.Source as Source
|
||||
import qualified Tags.Tagging.Precise as Tags
|
||||
|
||||
class ToTags t where
|
||||
@ -85,14 +85,14 @@ instance ToTags Rb.Class where
|
||||
name = Parse.Success expr,
|
||||
extraChildren
|
||||
} = enterScope True $ case expr of
|
||||
Prj Rb.Constant {text, ann} -> yield text ann
|
||||
Prj Rb.ScopeResolution {name = EPrj Rb.Constant {text, ann}} -> yield text ann
|
||||
Prj Rb.Constant {text, ann} -> yield text ann
|
||||
Prj Rb.ScopeResolution {name = EPrj Rb.Constant {text, ann}} -> yield text ann
|
||||
Prj Rb.ScopeResolution {name = EPrj Rb.Identifier {text, ann}} -> yield text ann
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
where
|
||||
range' = case extraChildren of
|
||||
EPrj Rb.Superclass {ann = Loc {byteRange = Range {end}}} : _ -> Range start end
|
||||
_ -> Range start (getEnd expr)
|
||||
_ -> Range start (getEnd expr)
|
||||
getEnd = Range.end . byteRange . TS.gann
|
||||
yield name loc = yieldTag name P.CLASS P.DEFINITION loc range' >> gtags t
|
||||
tags _ = pure ()
|
||||
@ -104,14 +104,14 @@ instance ToTags Rb.SingletonClass where
|
||||
value = Parse.Success (Rb.Arg expr),
|
||||
extraChildren
|
||||
} = enterScope True $ case expr of
|
||||
Prj (Rb.Primary (Prj (Rb.Lhs (Prj (Rb.Variable (Prj Rb.Constant {text, ann})))))) -> yield text ann
|
||||
Prj (Rb.Primary (Prj (Rb.Lhs (Prj Rb.ScopeResolution {name = EPrj Rb.Constant {text, ann}})))) -> yield text ann
|
||||
Prj (Rb.Primary (Prj (Rb.Lhs (Prj (Rb.Variable (Prj Rb.Constant {text, ann})))))) -> yield text ann
|
||||
Prj (Rb.Primary (Prj (Rb.Lhs (Prj Rb.ScopeResolution {name = EPrj Rb.Constant {text, ann}})))) -> yield text ann
|
||||
Prj (Rb.Primary (Prj (Rb.Lhs (Prj Rb.ScopeResolution {name = EPrj Rb.Identifier {text, ann}})))) -> yield text ann
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
where
|
||||
range' = case extraChildren of
|
||||
Parse.Success x : _ -> Range start (getStart x)
|
||||
_ -> range
|
||||
_ -> range
|
||||
getStart = Range.start . byteRange . TS.gann
|
||||
yield name loc = yieldTag name P.CLASS P.DEFINITION loc range' >> gtags t
|
||||
tags _ = pure ()
|
||||
@ -123,14 +123,14 @@ instance ToTags Rb.Module where
|
||||
name = Parse.Success expr,
|
||||
extraChildren
|
||||
} = enterScope True $ case expr of
|
||||
Prj Rb.Constant {text, ann} -> yield text ann
|
||||
Prj Rb.ScopeResolution {name = EPrj Rb.Constant {text, ann}} -> yield text ann
|
||||
Prj Rb.Constant {text, ann} -> yield text ann
|
||||
Prj Rb.ScopeResolution {name = EPrj Rb.Constant {text, ann}} -> yield text ann
|
||||
Prj Rb.ScopeResolution {name = EPrj Rb.Identifier {text, ann}} -> yield text ann
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
where
|
||||
range' = case extraChildren of
|
||||
Parse.Success x : _ -> Range start (getStart x)
|
||||
_ -> Range start (getEnd expr)
|
||||
_ -> Range start (getEnd expr)
|
||||
getEnd = Range.end . byteRange . TS.gann
|
||||
getStart = Range.start . byteRange . TS.gann
|
||||
yield name loc = yieldTag name P.MODULE P.DEFINITION loc range' >> gtags t
|
||||
@ -148,16 +148,16 @@ yieldMethodNameTag ::
|
||||
Rb.MethodName Loc ->
|
||||
m ()
|
||||
yieldMethodNameTag t range (Rb.MethodName expr) = enterScope True $ case expr of
|
||||
Prj Rb.Identifier {text, ann} -> yield text ann
|
||||
Prj Rb.Constant {text, ann} -> yield text ann
|
||||
Prj Rb.Identifier {text, ann} -> yield text ann
|
||||
Prj Rb.Constant {text, ann} -> yield text ann
|
||||
-- Prj Rb.ClassVariable { text = name } -> yield name
|
||||
Prj Rb.Operator {text, ann} -> yield text ann
|
||||
Prj Rb.Operator {text, ann} -> yield text ann
|
||||
-- Prj Rb.GlobalVariable { text = name } -> yield name
|
||||
-- Prj Rb.InstanceVariable { text = name } -> yield name
|
||||
Prj Rb.Setter {extraChildren = Parse.Success (Rb.Identifier {text, ann})} -> yield (text <> "=") ann-- NB: Matches existing tags output, TODO: Remove this.
|
||||
-- TODO: Should we report symbol method names as tags?
|
||||
-- Prj Rb.Symbol { extraChildren = [Prj Rb.EscapeSequence { text = name }] } -> yield name
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
where
|
||||
yield name loc = yieldTag name P.METHOD P.DEFINITION loc range >> gtags t
|
||||
|
||||
@ -178,7 +178,7 @@ instance ToTags Rb.Method where
|
||||
where
|
||||
range' = case parameters of
|
||||
Just (Parse.Success (Rb.MethodParameters {ann = Loc {byteRange = Range {end}}})) -> Range start end
|
||||
_ -> Range start (getEnd n)
|
||||
_ -> Range start (getEnd n)
|
||||
getEnd = Range.end . byteRange . TS.gann
|
||||
tags _ = pure ()
|
||||
|
||||
@ -192,7 +192,7 @@ instance ToTags Rb.SingletonMethod where
|
||||
where
|
||||
range' = case parameters of
|
||||
Just (Parse.Success (Rb.MethodParameters {ann = Loc {byteRange = Range {end}}})) -> Range start end
|
||||
_ -> Range start (getEnd n)
|
||||
_ -> Range start (getEnd n)
|
||||
getEnd = Range.end . byteRange . TS.gann
|
||||
tags _ = pure ()
|
||||
|
||||
@ -206,7 +206,7 @@ instance ToTags Rb.Lambda where
|
||||
tags Rb.Lambda {body = Parse.Success b, parameters} = enterScope False $ do
|
||||
case parameters of
|
||||
Just (Parse.Success p) -> tags p
|
||||
_ -> pure ()
|
||||
_ -> pure ()
|
||||
tags b
|
||||
tags _ = pure ()
|
||||
|
||||
@ -215,10 +215,10 @@ instance ToTags Rb.If where
|
||||
tags cond
|
||||
case consequence of
|
||||
Just (Parse.Success cons) -> tags cons
|
||||
_ -> pure ()
|
||||
_ -> pure ()
|
||||
case alternative of
|
||||
Just (Parse.Success alt) -> tags alt
|
||||
_ -> pure ()
|
||||
_ -> pure ()
|
||||
tags _ = pure ()
|
||||
|
||||
instance ToTags Rb.Elsif where
|
||||
@ -226,10 +226,10 @@ instance ToTags Rb.Elsif where
|
||||
tags cond
|
||||
case consequence of
|
||||
Just (Parse.Success cons) -> tags cons
|
||||
_ -> pure ()
|
||||
_ -> pure ()
|
||||
case alternative of
|
||||
Just (Parse.Success alt) -> tags alt
|
||||
_ -> pure ()
|
||||
_ -> pure ()
|
||||
tags _ = pure ()
|
||||
|
||||
instance ToTags Rb.Unless where
|
||||
@ -237,19 +237,19 @@ instance ToTags Rb.Unless where
|
||||
tags cond
|
||||
case consequence of
|
||||
Just (Parse.Success cons) -> tags cons
|
||||
_ -> pure ()
|
||||
_ -> pure ()
|
||||
case alternative of
|
||||
Just (Parse.Success alt) -> tags alt
|
||||
_ -> pure ()
|
||||
_ -> pure ()
|
||||
tags _ = pure ()
|
||||
|
||||
instance ToTags Rb.While where
|
||||
tags Rb.While {condition = Parse.Success cond, body = Parse.Success b} = tags cond >> tags b
|
||||
tags _ = pure ()
|
||||
tags _ = pure ()
|
||||
|
||||
instance ToTags Rb.Until where
|
||||
tags Rb.Until {condition = Parse.Success cond, body = Parse.Success b} = tags cond >> tags b
|
||||
tags _ = pure ()
|
||||
tags _ = pure ()
|
||||
|
||||
instance ToTags Rb.Regex where
|
||||
tags Rb.Regex {} = pure ()
|
||||
@ -263,9 +263,9 @@ instance ToTags Rb.Lhs where
|
||||
-- NOTE: Calls do not look for locals
|
||||
Prj Rb.Call {ann = Loc {byteRange}, method} -> case method of
|
||||
EPrj Rb.Identifier {text, ann} -> yieldCall text ann byteRange
|
||||
EPrj Rb.Constant {text, ann} -> yieldCall text ann byteRange
|
||||
EPrj Rb.Operator {text, ann} -> yieldCall text ann byteRange
|
||||
_ -> gtags t
|
||||
EPrj Rb.Constant {text, ann} -> yieldCall text ann byteRange
|
||||
EPrj 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 P.CALL loc byteRange
|
||||
Prj Rb.ScopeResolution {ann = loc@Loc {byteRange}, name = EPrj Rb.Identifier {text}} -> yield text P.CALL loc byteRange
|
||||
@ -292,9 +292,9 @@ instance ToTags Rb.MethodCall where
|
||||
EPrj Rb.ScopeResolution {name = EPrj Rb.Constant {text, ann}} -> yield text P.CALL ann -- TODO: Should yield Constant
|
||||
EPrj Rb.Call {method} -> case method of
|
||||
EPrj Rb.Identifier {text, ann} -> yield text P.CALL ann
|
||||
EPrj Rb.Constant {text, ann} -> yield text P.CALL ann
|
||||
EPrj Rb.Operator {text, ann} -> yield text P.CALL ann
|
||||
_ -> gtags t
|
||||
EPrj Rb.Constant {text, ann} -> yield text P.CALL ann
|
||||
EPrj Rb.Operator {text, ann} -> yield text P.CALL ann
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
where
|
||||
yield name kind loc = yieldTag name kind P.REFERENCE loc byteRange >> gtags t
|
||||
@ -308,10 +308,10 @@ instance ToTags Rb.Alias where
|
||||
} = do
|
||||
case aliasExpr of
|
||||
Prj Rb.Identifier {ann, text} -> yieldTag text P.FUNCTION P.DEFINITION ann byteRange
|
||||
_ -> tags aliasExpr
|
||||
_ -> tags aliasExpr
|
||||
case nameExpr of
|
||||
Prj Rb.Identifier {ann, text} -> yieldTag text P.CALL P.REFERENCE ann byteRange
|
||||
_ -> tags nameExpr
|
||||
_ -> tags nameExpr
|
||||
gtags t
|
||||
tags _ = pure ()
|
||||
|
||||
@ -326,7 +326,7 @@ instance ToTags Rb.Undef where
|
||||
Parse.Success (Rb.MethodName expr) -> do
|
||||
case expr of
|
||||
Prj Rb.Identifier {ann, text} -> yieldTag text P.CALL P.REFERENCE ann byteRange
|
||||
_ -> tags expr
|
||||
_ -> tags expr
|
||||
Parse.Fail _ -> pure ()
|
||||
gtags t
|
||||
|
||||
@ -376,8 +376,8 @@ instance ToTags Rb.Assignment where
|
||||
tags t@Rb.Assignment {left} = do
|
||||
case left of
|
||||
EPrj (Rb.Lhs (Prj (Rb.Variable (Prj Rb.Identifier {text})))) -> modify (text :)
|
||||
EPrj Rb.LeftAssignmentList {extraChildren} -> introduceLhsLocals extraChildren
|
||||
_ -> pure ()
|
||||
EPrj Rb.LeftAssignmentList {extraChildren} -> introduceLhsLocals extraChildren
|
||||
_ -> pure ()
|
||||
gtags t
|
||||
where
|
||||
introduceLhsLocals xs = for_ xs $ \x -> case x of
|
||||
@ -390,7 +390,7 @@ instance ToTags Rb.OperatorAssignment where
|
||||
tags t@Rb.OperatorAssignment {left} = do
|
||||
case left of
|
||||
EPrj (Rb.Lhs (Prj (Rb.Variable (Prj Rb.Identifier {text})))) -> modify (text :)
|
||||
_ -> pure ()
|
||||
_ -> pure ()
|
||||
gtags t
|
||||
|
||||
gtags ::
|
||||
|
@ -11,19 +11,19 @@ module Language.TSX.Tags
|
||||
)
|
||||
where
|
||||
|
||||
import AST.Element
|
||||
import AST.Element
|
||||
import qualified AST.Parse as Parse
|
||||
import AST.Token
|
||||
import AST.Traversable1
|
||||
import Control.Effect.Reader
|
||||
import Control.Effect.Writer
|
||||
import Control.Effect.State
|
||||
import Data.Foldable
|
||||
import Data.Text as Text
|
||||
import AST.Token
|
||||
import AST.Traversable1
|
||||
import Control.Effect.Reader
|
||||
import Control.Effect.State
|
||||
import Control.Effect.Writer
|
||||
import Data.Foldable
|
||||
import Data.Text as Text hiding (elem)
|
||||
import qualified Language.TSX.AST as Tsx
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Source as Source
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Source as Source
|
||||
import qualified Tags.Tagging.Precise as Tags
|
||||
|
||||
class ToTags t where
|
||||
@ -62,13 +62,13 @@ instance ToTags Tsx.FunctionDeclaration where
|
||||
instance ToTags Tsx.MethodDefinition where
|
||||
tags t@Tsx.MethodDefinition {ann = Loc {byteRange}, name} = case name of
|
||||
EPrj Tsx.PropertyIdentifier {text, ann} -> yieldTag text P.METHOD P.DEFINITION ann byteRange >> gtags t
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
|
||||
instance ToTags Tsx.Pair where
|
||||
tags t@Tsx.Pair {ann = Loc {byteRange}, key, value = Parse.Success (Tsx.Expression expr)} = case (key, expr) of
|
||||
(EPrj Tsx.PropertyIdentifier {text, ann}, Prj Tsx.Function {}) -> yield text ann
|
||||
(EPrj Tsx.PropertyIdentifier {text, ann}, Prj Tsx.Function {}) -> yield text ann
|
||||
(EPrj Tsx.PropertyIdentifier {text, ann}, Prj Tsx.ArrowFunction {}) -> yield text ann
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
where
|
||||
yield text loc = yieldTag text P.FUNCTION P.DEFINITION loc byteRange >> gtags t
|
||||
tags _ = pure ()
|
||||
@ -89,8 +89,8 @@ instance ToTags Tsx.CallExpression where
|
||||
Prj Tsx.Function {name = Just (Parse.Success (Tsx.Identifier {text, ann}))} -> yield text ann
|
||||
Prj Tsx.ParenthesizedExpression {extraChildren} -> for_ extraChildren $ \x -> case x of
|
||||
EPrj (Tsx.Expression expr) -> match expr
|
||||
Parse.Success x -> tags x
|
||||
Parse.Fail _ -> pure ()
|
||||
Parse.Success x -> tags x
|
||||
Parse.Fail _ -> pure ()
|
||||
_ -> gtags t
|
||||
yield name loc = yieldTag name P.CALL P.REFERENCE loc byteRange >> gtags t
|
||||
tags _ = pure ()
|
||||
@ -103,14 +103,14 @@ instance ToTags Tsx.Class where
|
||||
instance ToTags Tsx.Module where
|
||||
tags t@Tsx.Module {ann = Loc {byteRange}, name} = case name of
|
||||
EPrj Tsx.Identifier {text, ann} -> yieldTag text P.MODULE P.DEFINITION ann byteRange >> gtags t
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
|
||||
instance ToTags Tsx.VariableDeclarator where
|
||||
tags t@Tsx.VariableDeclarator {ann = Loc {byteRange}, name, value = Just (Parse.Success (Tsx.Expression expr))} =
|
||||
case (expr, name) of
|
||||
(Prj Tsx.Function {}, EPrj Tsx.Identifier {text, ann}) -> yield text ann
|
||||
(Prj Tsx.Function {}, EPrj Tsx.Identifier {text, ann}) -> yield text ann
|
||||
(Prj Tsx.ArrowFunction {}, EPrj Tsx.Identifier {text, ann}) -> yield text ann
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
where
|
||||
yield text loc = yieldTag text P.FUNCTION P.DEFINITION loc byteRange >> gtags t
|
||||
tags t = gtags t
|
||||
|
@ -14,19 +14,19 @@ module Language.TypeScript.Tags
|
||||
)
|
||||
where
|
||||
|
||||
import AST.Element
|
||||
import AST.Element
|
||||
import qualified AST.Parse as Parse
|
||||
import AST.Token
|
||||
import AST.Traversable1
|
||||
import Control.Effect.Reader
|
||||
import Control.Effect.Writer
|
||||
import Control.Effect.State
|
||||
import Data.Foldable
|
||||
import Data.Text as Text
|
||||
import AST.Token
|
||||
import AST.Traversable1
|
||||
import Control.Effect.Reader
|
||||
import Control.Effect.State
|
||||
import Control.Effect.Writer
|
||||
import Data.Foldable
|
||||
import Data.Text as Text hiding (elem)
|
||||
import qualified Language.TypeScript.AST as Ts
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Source as Source
|
||||
import Proto.Semantic as P
|
||||
import Source.Loc
|
||||
import Source.Source as Source
|
||||
import qualified Tags.Tagging.Precise as Tags
|
||||
|
||||
class ToTags (t :: * -> *) where
|
||||
@ -70,9 +70,9 @@ instance ToTags Ts.MethodDefinition where
|
||||
|
||||
instance ToTags Ts.Pair where
|
||||
tags t@Ts.Pair {ann = Loc {byteRange}, key = Parse.Success key, value = Parse.Success (Ts.Expression expr)} = case (key, expr) of
|
||||
(Prj Ts.PropertyIdentifier {text, ann}, Prj Ts.Function {}) -> yield text ann
|
||||
(Prj Ts.PropertyIdentifier {text, ann}, Prj Ts.Function {}) -> yield text ann
|
||||
(Prj Ts.PropertyIdentifier {text, ann}, Prj Ts.ArrowFunction {}) -> yield text ann
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
where
|
||||
yield text loc = yieldTag text P.FUNCTION P.DEFINITION loc byteRange >> gtags t
|
||||
tags _ = pure ()
|
||||
@ -93,8 +93,8 @@ instance ToTags Ts.CallExpression where
|
||||
Prj Ts.Function {name = Just (Parse.Success (Ts.Identifier {text, ann}))} -> yield text ann
|
||||
Prj Ts.ParenthesizedExpression {extraChildren} -> for_ extraChildren $ \x -> case x of
|
||||
EPrj (Ts.Expression expr) -> match expr
|
||||
Parse.Success x -> tags x
|
||||
Parse.Fail _ -> pure ()
|
||||
Parse.Success x -> tags x
|
||||
Parse.Fail _ -> pure ()
|
||||
_ -> gtags t
|
||||
yield name loc = yieldTag name P.CALL P.REFERENCE loc byteRange >> gtags t
|
||||
tags _ = pure ()
|
||||
@ -107,14 +107,14 @@ instance ToTags Ts.Class where
|
||||
instance ToTags Ts.Module where
|
||||
tags t@Ts.Module {ann = Loc {byteRange}, name} = case name of
|
||||
Parse.Success (Prj Ts.Identifier {text, ann}) -> yieldTag text P.MODULE P.DEFINITION ann byteRange >> gtags t
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
|
||||
instance ToTags Ts.VariableDeclarator where
|
||||
tags t@Ts.VariableDeclarator {ann = Loc {byteRange}, name, value = Just (Parse.Success (Ts.Expression expr))} =
|
||||
case (expr, name) of
|
||||
(Prj Ts.Function {}, Parse.Success (Prj Ts.Identifier {text, ann})) -> yield text ann
|
||||
(Prj Ts.Function {}, Parse.Success (Prj Ts.Identifier {text, ann})) -> yield text ann
|
||||
(Prj Ts.ArrowFunction {}, Parse.Success (Prj Ts.Identifier {text, ann})) -> yield text ann
|
||||
_ -> gtags t
|
||||
_ -> gtags t
|
||||
where
|
||||
yield text loc = yieldTag text P.FUNCTION P.DEFINITION loc byteRange >> gtags t
|
||||
tags t = gtags t
|
||||
|
Loading…
Reference in New Issue
Block a user