mirror of
https://github.com/github/semantic.git
synced 2024-11-24 00:42:33 +03:00
Bring javascript/typescript up-to-speed
This commit is contained in:
parent
0db7d34947
commit
8de86acc31
@ -5,6 +5,7 @@
|
|||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE NamedFieldPuns #-}
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE PartialTypeSignatures #-}
|
{-# LANGUAGE PartialTypeSignatures #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
@ -142,7 +143,16 @@ gtags = getAp . Tags.gfoldMap1 @ToTags (Ap . tags) . from1
|
|||||||
instance (Generic1 t, Tags.GFoldable1 ToTags (Rep1 t)) => ToTagsBy 'Generic t where
|
instance (Generic1 t, Tags.GFoldable1 ToTags (Rep1 t)) => ToTagsBy 'Generic t where
|
||||||
tags' = gtags
|
tags' = gtags
|
||||||
|
|
||||||
|
-- These are all valid, but point to built-in functions (e.g. require) that a la
|
||||||
|
-- carte doesn't display and since we have nothing to link to yet (can't
|
||||||
|
-- jump-to-def), we hide them from the current tags output.
|
||||||
|
nameBlacklist :: [Text]
|
||||||
|
nameBlacklist =
|
||||||
|
[ "require"
|
||||||
|
]
|
||||||
|
|
||||||
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 -> Kind -> Loc -> Range -> m ()
|
||||||
|
yieldTag name Call _ _ | name `elem` nameBlacklist = pure ()
|
||||||
yieldTag name kind loc range = do
|
yieldTag name kind loc range = do
|
||||||
src <- ask @Source
|
src <- ask @Source
|
||||||
let sliced = slice src range
|
let sliced = slice src range
|
||||||
|
@ -5,6 +5,7 @@
|
|||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE NamedFieldPuns #-}
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE PartialTypeSignatures #-}
|
{-# LANGUAGE PartialTypeSignatures #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
@ -134,7 +135,16 @@ gtags = getAp . Tags.gfoldMap1 @ToTags (Ap . tags) . from1
|
|||||||
instance (Generic1 t, Tags.GFoldable1 ToTags (Rep1 t)) => ToTagsBy 'Generic t where
|
instance (Generic1 t, Tags.GFoldable1 ToTags (Rep1 t)) => ToTagsBy 'Generic t where
|
||||||
tags' = gtags
|
tags' = gtags
|
||||||
|
|
||||||
|
-- These are all valid, but point to built-in functions (e.g. require) that a la
|
||||||
|
-- carte doesn't display and since we have nothing to link to yet (can't
|
||||||
|
-- jump-to-def), we hide them from the current tags output.
|
||||||
|
nameBlacklist :: [Text]
|
||||||
|
nameBlacklist =
|
||||||
|
[ "require"
|
||||||
|
]
|
||||||
|
|
||||||
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 -> Kind -> Loc -> Range -> m ()
|
||||||
|
yieldTag name Call _ _ | name `elem` nameBlacklist = pure ()
|
||||||
yieldTag name kind loc range = do
|
yieldTag name kind loc range = do
|
||||||
src <- ask @Source
|
src <- ask @Source
|
||||||
let sliced = slice src range
|
let sliced = slice src range
|
||||||
|
@ -100,7 +100,7 @@ tagsForBlob :: (Has (Error SomeException) sig m, Has Parse sig m, Has (Reader Pe
|
|||||||
tagsForBlob blob = asks toTagsParsers >>= \p -> parseWith p (pure . tags symbolsToSummarize blob) blob
|
tagsForBlob blob = asks toTagsParsers >>= \p -> parseWith p (pure . tags symbolsToSummarize blob) blob
|
||||||
|
|
||||||
symbolsToSummarize :: [Text]
|
symbolsToSummarize :: [Text]
|
||||||
symbolsToSummarize = ["Function", "Method", "Class", "Module", "Call", "Send"]
|
symbolsToSummarize = ["Function", "AmbientFunction", "Method", "Class", "Module", "Call", "Send"]
|
||||||
|
|
||||||
class ToTags t where
|
class ToTags t where
|
||||||
tags :: [Text] -> Blob -> t Loc -> [Tag]
|
tags :: [Text] -> Blob -> t Loc -> [Tag]
|
||||||
|
@ -142,8 +142,10 @@ type family TaggableInstance (t :: * -> *) :: Strategy where
|
|||||||
TaggableInstance Ruby.Class = 'Custom
|
TaggableInstance Ruby.Class = 'Custom
|
||||||
TaggableInstance Ruby.Module = 'Custom
|
TaggableInstance Ruby.Module = 'Custom
|
||||||
TaggableInstance TypeScript.Module = 'Custom
|
TaggableInstance TypeScript.Module = 'Custom
|
||||||
|
TaggableInstance TypeScript.AmbientFunction = 'Custom
|
||||||
TaggableInstance Expression.Call = 'Custom
|
TaggableInstance Expression.Call = 'Custom
|
||||||
TaggableInstance Ruby.Send = 'Custom
|
TaggableInstance Ruby.Send = 'Custom
|
||||||
|
|
||||||
TaggableInstance _ = 'Default
|
TaggableInstance _ = 'Default
|
||||||
|
|
||||||
instance TaggableBy 'Default t
|
instance TaggableBy 'Default t
|
||||||
@ -172,6 +174,10 @@ instance TaggableBy 'Custom Declaration.Function where
|
|||||||
snippet' ann (Declaration.Function _ _ _ body) = subtractLoc ann (termAnnotation body)
|
snippet' ann (Declaration.Function _ _ _ body) = subtractLoc ann (termAnnotation body)
|
||||||
symbolName' = declaredName . Declaration.functionName
|
symbolName' = declaredName . Declaration.functionName
|
||||||
|
|
||||||
|
instance TaggableBy 'Custom TypeScript.AmbientFunction where
|
||||||
|
snippet' ann _ = byteRange ann
|
||||||
|
symbolName' = declaredName . TypeScript.ambientFunctionIdentifier
|
||||||
|
|
||||||
instance TaggableBy 'Custom Declaration.Method where
|
instance TaggableBy 'Custom Declaration.Method where
|
||||||
docsLiteral' Python (Declaration.Method _ _ _ _ body _)
|
docsLiteral' Python (Declaration.Method _ _ _ _ body _)
|
||||||
| bodyF <- termOut body
|
| bodyF <- termOut body
|
||||||
|
@ -45,6 +45,7 @@ runTagging lang symbolsToSummarize source
|
|||||||
"Module" -> Just Module
|
"Module" -> Just Module
|
||||||
"Call" -> Just Call
|
"Call" -> Just Call
|
||||||
"Send" -> Just Call -- Ruby’s Send is considered to be a kind of 'Call'
|
"Send" -> Just Call -- Ruby’s Send is considered to be a kind of 'Call'
|
||||||
|
"AmbientFunction" -> Just Function -- Classify TypeScript ambient functions as 'Function'
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
type ContextToken = (Text, Range)
|
type ContextToken = (Text, Range)
|
||||||
|
Loading…
Reference in New Issue
Block a user