Skip to content

Commit 37925a0

Browse files
soulomoonfendormichaelpj
authored
Implement semantic tokens plugin to support semantic highlighting(textDocument/semanticTokens/full) (#3892)
* Implement semantic tokens lsp plugin draft * SemanticTokens: combine information extracted from HieAst * clean up * map to default token types in lsp * use lsp makeSemanticTokens to convert to lsp SemanticTokens type * add test and cleanup * refine semantic type to default one in lsp * Use tokens from hieAst instead of renamedSource and add test * use customize RefMap to get semantic type * use refMap from useAsts * Also compute imported names * Also compute semantic type from TyThing * Fix dependencies version * fix version * Retrieve nameSet from renamedSource to prevent names not visible(Such as by instance deriving) being handled * add hlint config to ignore test data * cean up test data * revert flake.nix * Rename query.hs to Query.hs * Build: add semantic tokens to lts21 * Refactor and add README * Semantic token, filter names in Ast * CI: add consistancy check for wether semantic tokens computations is stable across different ghc versions * Update documentation, cleanup test, remove default modifiers * Fix: IO now classfied to TTypcon, add test for GADT and data family, Update documentation * Restore stack.yaml * fix stack build * Refactor, move out ActualToken to Mappings and use ide logger * Refactor: toLspTokenType should return Maybe type * Stop use stale hieAst * add getImportedNameSemanticRule rule to semantic tokens plugin * do not retrieve hie in getImportedNameSemanticRule * fix: add description for semantic tokens * remove TValBind and TPaternBind and Use TFunction and TVariable instead * cleanup * Refactor useWithStaleMT and took care of the token range using position map * fix build for 9.4 * refactor, use golden test * refactor, use ExceptT for computeSemanticTokens * Fix 9.2 * add persistentSemanticMapRule to prevent semantic tokens block on startup * Fix, use hieKind instead of cast the type directly * add options to turn semantic tokens on and off * Disable stan plugin by default (#3917) * Fix positionMapping in stale data (#3920) * Fix positionMapping in stale data * add test for updatePositionMapping * add comment to demonstrate addOldDelta * cleanup * fix: for local variable, extract type from contextInfo instead of bind site, thus function in pattern binds can also be indentified * clean up * Update plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Query.hs Co-authored-by: Michael Peyton Jones <me@michaelpj.com> * refactor: remove TNothing and compact the test output * refactor: rename SemanticTokenType to HsSemanticTokenType to avoid confusion with lsp' SemanticTokenTypes * refactor: push the computation of semantic token type to getSemanticTokensRule * update documentation * cleanup hieAstSpanNames * remove renamed source from getSemanticTokensRule and optimize query function for semantic token type * try to exclude names that is not visible in hie and cleanup * add HieFunMaskKind, it is to differ wether a type at type index is a function or non-function * expose function flag to expose (=>, ->, -=>, ==>) * 1. Relax GetDocMap kindMap to get TyThing for more than type variables. 2. Backport isVisibleFunArg * use customize logger, add test for unicode * fix: handle unicode in semantic tokens * update KindMap to TyThingMap * cleanup * add realSrcSpanToCodePointRange, realSrcLocToCodePointPosition to Development.IDE.GHC.Error * add Note [Semantic information from Multiple Sources] * move recoverFunMaskArray to Mappings.hs * fix test, data.Set might not appear * fix: handle semantic tokens with more than one ast * fix: instance PluginMethod Request Method_TextDocumentSemanticTokensFull * clean up * turn semantic tokens off by default * fix doc * clean up doc --------- Co-authored-by: fendor <fendor@users.noreply.github.com> Co-authored-by: Michael Peyton Jones <me@michaelpj.com>
1 parent 9741233 commit 37925a0

File tree

76 files changed

+1756
-25
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

76 files changed

+1756
-25
lines changed

cabal.project

+5-4
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,7 @@ packages:
3434
./plugins/hls-explicit-record-fields-plugin
3535
./plugins/hls-refactor-plugin
3636
./plugins/hls-overloaded-record-dot-plugin
37+
./plugins/hls-semantic-tokens-plugin
3738

3839
index-state: 2023-12-13T00:00:00Z
3940

@@ -55,8 +56,8 @@ constraints:
5556
text -simdutf,
5657
ghc-check -ghc-check-use-package-abis,
5758
ghc-lib-parser-ex -auto,
58-
-- This is only present in some versions, and it's on by default since
59-
-- 0.14.5.0, but there are some versions we allow that need this
59+
-- This is only present in some versions, and it's on by default since
60+
-- 0.14.5.0, but there are some versions we allow that need this
6061
-- setting
6162
stylish-haskell +ghc-lib,
6263
-- Centos 7 comes with an old gcc version that doesn't know about
@@ -79,8 +80,8 @@ source-repository-package
7980
-- END DELETE
8081

8182
if impl(ghc >= 9.1)
82-
-- ekg packagess are old and unmaintained, but we
83-
-- don't rely on them for the mainline build, so
83+
-- ekg packagess are old and unmaintained, but we
84+
-- don't rely on them for the mainline build, so
8485
-- this is okay
8586
allow-newer:
8687
ekg-json:base,

ghcide/src/Development/IDE/Core/RuleTypes.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -238,14 +238,14 @@ type instance RuleResult GetHieAst = HieAstResult
238238
-- | A IntervalMap telling us what is in scope at each point
239239
type instance RuleResult GetBindings = Bindings
240240

241-
data DocAndKindMap = DKMap {getDocMap :: !DocMap, getKindMap :: !KindMap}
242-
instance NFData DocAndKindMap where
241+
data DocAndTyThingMap = DKMap {getDocMap :: !DocMap, getTyThingMap :: !TyThingMap}
242+
instance NFData DocAndTyThingMap where
243243
rnf (DKMap a b) = rwhnf a `seq` rwhnf b
244244

245-
instance Show DocAndKindMap where
245+
instance Show DocAndTyThingMap where
246246
show = const "docmap"
247247

248-
type instance RuleResult GetDocMap = DocAndKindMap
248+
type instance RuleResult GetDocMap = DocAndTyThingMap
249249

250250
-- | A GHC session that we reuse.
251251
type instance RuleResult GhcSession = HscEnvEq

ghcide/src/Development/IDE/GHC/Compat/Core.hs

+19-7
Original file line numberDiff line numberDiff line change
@@ -407,6 +407,7 @@ module Development.IDE.GHC.Compat.Core (
407407
field_label,
408408
#endif
409409
groupOrigin,
410+
isVisibleFunArg,
410411
) where
411412

412413
import qualified GHC
@@ -431,13 +432,13 @@ import GHC.Core.DataCon hiding (dataConExTyCoVars)
431432
import qualified GHC.Core.DataCon as DataCon
432433
import GHC.Core.FamInstEnv hiding (pprFamInst)
433434
import GHC.Core.InstEnv
434-
import GHC.Types.Unique.FM
435+
import GHC.Types.Unique.FM
435436
import GHC.Core.PatSyn
436437
import GHC.Core.Predicate
437438
import GHC.Core.TyCo.Ppr
438439
import qualified GHC.Core.TyCo.Rep as TyCoRep
439440
import GHC.Core.TyCon
440-
import GHC.Core.Type
441+
import GHC.Core.Type
441442
import GHC.Core.Unify
442443
import GHC.Core.Utils
443444
import GHC.Driver.CmdLine (Warn (..))
@@ -489,6 +490,8 @@ import qualified GHC.Types.SrcLoc as SrcLoc
489490
import GHC.Types.Unique.Supply
490491
import GHC.Types.Var (Var (varName), setTyVarUnique,
491492
setVarUnique)
493+
494+
import qualified GHC.Types.Var as TypesVar
492495
import GHC.Unit.Info (PackageName (..))
493496
import GHC.Unit.Module hiding (ModLocation (..), UnitId,
494497
moduleUnit,
@@ -597,7 +600,7 @@ pattern RealSrcLoc x y = SrcLoc.RealSrcLoc x y
597600
pattern AvailTC :: Name -> [Name] -> [FieldLabel] -> Avail.AvailInfo
598601
#if __GLASGOW_HASKELL__ >= 907
599602
pattern AvailTC n names pieces <- Avail.AvailTC n ((,[]) -> (names,pieces))
600-
#else
603+
#else
601604
pattern AvailTC n names pieces <- Avail.AvailTC n ((\gres -> foldr (\gre (names, pieces) -> case gre of
602605
Avail.NormalGreName name -> (name: names, pieces)
603606
Avail.FieldGreName label -> (names, label:pieces)) ([], []) gres) -> (names, pieces))
@@ -606,14 +609,14 @@ pattern AvailTC n names pieces <- Avail.AvailTC n ((\gres -> foldr (\gre (names,
606609
pattern AvailName :: Name -> Avail.AvailInfo
607610
#if __GLASGOW_HASKELL__ >= 907
608611
pattern AvailName n <- Avail.Avail n
609-
#else
612+
#else
610613
pattern AvailName n <- Avail.Avail (Avail.NormalGreName n)
611614
#endif
612615

613616
pattern AvailFL :: FieldLabel -> Avail.AvailInfo
614617
#if __GLASGOW_HASKELL__ >= 907
615618
pattern AvailFL fl <- (const Nothing -> Just fl) -- this pattern always fails as this field was removed in 9.7
616-
#else
619+
#else
617620
pattern AvailFL fl <- Avail.Avail (Avail.FieldGreName fl)
618621
#endif
619622

@@ -630,8 +633,17 @@ pattern ExposePackage s a mr <- DynFlags.ExposePackage s a _ mr
630633
pattern ExposePackage s a mr = DynFlags.ExposePackage s a mr
631634
#endif
632635

633-
pattern FunTy :: Type -> Type -> Type
634-
pattern FunTy arg res <- TyCoRep.FunTy {ft_arg = arg, ft_res = res}
636+
#if __GLASGOW_HASKELL__ >= 906
637+
isVisibleFunArg = TypesVar.isVisibleFunArg
638+
type FunTyFlag = TypesVar.FunTyFlag
639+
#else
640+
isVisibleFunArg VisArg = True
641+
isVisibleFunArg _ = False
642+
type FunTyFlag = TypesVar.AnonArgFlag
643+
#endif
644+
pattern FunTy :: Development.IDE.GHC.Compat.Core.FunTyFlag -> Type -> Type -> Type
645+
pattern FunTy af arg res <- TyCoRep.FunTy {ft_af = af, ft_arg = arg, ft_res = res}
646+
635647

636648
-- type HasSrcSpan x a = (GenLocated SrcSpan a ~ x)
637649
-- type HasSrcSpan x = () :: Constraint

ghcide/src/Development/IDE/GHC/Error.hs

+26
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,8 @@ module Development.IDE.GHC.Error
1717
, realSrcSpanToRange
1818
, realSrcLocToPosition
1919
, realSrcSpanToLocation
20+
, realSrcSpanToCodePointRange
21+
, realSrcLocToCodePointPosition
2022
, srcSpanToFilename
2123
, rangeToSrcSpan
2224
, rangeToRealSrcSpan
@@ -45,6 +47,8 @@ import Development.IDE.Types.Diagnostics as D
4547
import Development.IDE.Types.Location
4648
import GHC
4749
import Language.LSP.Protocol.Types (isSubrangeOf)
50+
import Language.LSP.VFS (CodePointPosition (CodePointPosition),
51+
CodePointRange (CodePointRange))
4852

4953

5054
diagFromText :: T.Text -> D.DiagnosticSeverity -> SrcSpan -> T.Text -> FileDiagnostic
@@ -86,6 +90,28 @@ realSrcLocToPosition :: RealSrcLoc -> Position
8690
realSrcLocToPosition real =
8791
Position (fromIntegral $ srcLocLine real - 1) (fromIntegral $ srcLocCol real - 1)
8892

93+
-- Note [Unicode support]
94+
-- the current situation is:
95+
-- LSP Positions use UTF-16 code units(Unicode may count as variable columns);
96+
-- GHC use Unicode code points(Unicode count as one column).
97+
-- To support unicode, ideally range should be in lsp standard,
98+
-- and codePoint should be in ghc standard.
99+
-- see https://github.com/haskell/lsp/pull/407
100+
101+
-- | Convert a GHC SrcSpan to CodePointRange
102+
-- see Note [Unicode support]
103+
realSrcSpanToCodePointRange :: RealSrcSpan -> CodePointRange
104+
realSrcSpanToCodePointRange real =
105+
CodePointRange
106+
(realSrcLocToCodePointPosition $ Compat.realSrcSpanStart real)
107+
(realSrcLocToCodePointPosition $ Compat.realSrcSpanEnd real)
108+
109+
-- | Convert a GHC RealSrcLoc to CodePointPosition
110+
-- see Note [Unicode support]
111+
realSrcLocToCodePointPosition :: RealSrcLoc -> CodePointPosition
112+
realSrcLocToCodePointPosition real =
113+
CodePointPosition (fromIntegral $ srcLocLine real - 1) (fromIntegral $ srcLocCol real - 1)
114+
89115
-- | Extract a file name from a GHC SrcSpan (use message for unhelpful ones)
90116
-- FIXME This may not be an _absolute_ file name, needs fixing.
91117
srcSpanToFilename :: SrcSpan -> Maybe FilePath

ghcide/src/Development/IDE/Plugin/Completions.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -144,8 +144,8 @@ resolveCompletion ide _pid comp@CompletionItem{_detail,_documentation,_data_} ur
144144
#endif
145145
mdkm <- liftIO $ runIdeAction "CompletionResolve.GetDocMap" (shakeExtras ide) $ useWithStaleFast GetDocMap file
146146
let (dm,km) = case mdkm of
147-
Just (DKMap docMap kindMap, _) -> (docMap,kindMap)
148-
Nothing -> (mempty, mempty)
147+
Just (DKMap docMap tyThingMap, _) -> (docMap,tyThingMap)
148+
Nothing -> (mempty, mempty)
149149
doc <- case lookupNameEnv dm name of
150150
Just doc -> pure $ spanDocToMarkdown doc
151151
Nothing -> liftIO $ spanDocToMarkdown <$> getDocumentationTryGhc (hscEnv sess) name

ghcide/src/Development/IDE/Spans/AtPoint.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -209,7 +209,7 @@ gotoDefinition withHieDb getHieFile ideOpts imports srcSpans pos
209209
atPoint
210210
:: IdeOptions
211211
-> HieAstResult
212-
-> DocAndKindMap
212+
-> DocAndTyThingMap
213213
-> HscEnv
214214
-> Position
215215
-> IO (Maybe (Maybe Range, [T.Text]))
@@ -346,7 +346,7 @@ namesInType (TyVarTy n) = [varName n]
346346
namesInType (AppTy a b) = getTypes [a,b]
347347
namesInType (TyConApp tc ts) = tyConName tc : getTypes ts
348348
namesInType (ForAllTy b t) = varName (binderVar b) : namesInType t
349-
namesInType (FunTy a b) = getTypes [a,b]
349+
namesInType (FunTy _ a b) = getTypes [a,b]
350350
namesInType (CastTy t _) = namesInType t
351351
namesInType (LitTy _) = []
352352
namesInType _ = []

ghcide/src/Development/IDE/Spans/Common.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ module Development.IDE.Spans.Common (
1212
, spanDocToMarkdown
1313
, spanDocToMarkdownForTest
1414
, DocMap
15-
, KindMap
15+
, TyThingMap
1616
) where
1717

1818
import Control.DeepSeq
@@ -31,7 +31,7 @@ import qualified Documentation.Haddock.Parser as H
3131
import qualified Documentation.Haddock.Types as H
3232

3333
type DocMap = NameEnv SpanDoc
34-
type KindMap = NameEnv TyThing
34+
type TyThingMap = NameEnv TyThing
3535

3636
-- | Shows IEWrappedName, without any modifier, qualifier or unique identifier.
3737
#if MIN_VERSION_ghc(9,5,0)

ghcide/src/Development/IDE/Spans/Documentation.hs

+2-3
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@ mkDocMap
3939
:: HscEnv
4040
-> RefMap a
4141
-> TcGblEnv
42-
-> IO DocAndKindMap
42+
-> IO DocAndTyThingMap
4343
mkDocMap env rm this_mod =
4444
do
4545
#if MIN_VERSION_ghc(9,3,0)
@@ -61,8 +61,7 @@ mkDocMap env rm this_mod =
6161
doc <- getDocumentationTryGhc env n
6262
pure $ extendNameEnv nameMap n doc
6363
getType n nameMap
64-
| isTcOcc $ occName n
65-
, Nothing <- lookupNameEnv nameMap n
64+
| Nothing <- lookupNameEnv nameMap n
6665
= do kind <- lookupKind env n
6766
pure $ maybe nameMap (extendNameEnv nameMap n) kind
6867
| otherwise = pure nameMap

haskell-language-server.cabal

+12
Original file line numberDiff line numberDiff line change
@@ -164,6 +164,11 @@ flag overloadedRecordDot
164164
default: True
165165
manual: True
166166

167+
flag semanticTokens
168+
description: Enable semantic tokens plugin
169+
default: True
170+
manual: True
171+
167172
-- formatters
168173

169174
flag floskell
@@ -333,6 +338,12 @@ common refactor
333338
build-depends: hls-refactor-plugin == 2.5.0.0
334339
cpp-options: -Dhls_refactor
335340

341+
common semanticTokens
342+
if flag(semanticTokens)
343+
build-depends: hls-semantic-tokens-plugin == 2.5.0.0
344+
cpp-options: -Dhls_semanticTokens
345+
346+
336347
library
337348
import: common-deps
338349
-- configuration
@@ -365,6 +376,7 @@ library
365376
, stylishHaskell
366377
, refactor
367378
, overloadedRecordDot
379+
, semanticTokens
368380

369381
exposed-modules:
370382
Ide.Arguments

hls-plugin-api/src/Ide/Plugin/Config.hs

+1
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,7 @@ parsePluginConfig :: PluginConfig -> Value -> A.Parser PluginConfig
6666
parsePluginConfig def = A.withObject "PluginConfig" $ \o -> PluginConfig
6767
<$> o .:? "globalOn" .!= plcGlobalOn def
6868
<*> o .:? "callHierarchyOn" .!= plcCallHierarchyOn def
69+
<*> o .:? "semanticTokensOn" .!= plcSemanticTokensOn def
6970
<*> o .:? "codeActionsOn" .!= plcCodeActionsOn def
7071
<*> o .:? "codeLensOn" .!= plcCodeLensOn def
7172
<*> o .:? "diagnosticsOn" .!= plcDiagnosticsOn def -- AZ

hls-plugin-api/src/Ide/Plugin/ConfigUtils.hs

+2
Original file line numberDiff line numberDiff line change
@@ -93,6 +93,7 @@ pluginsToDefaultConfig IdePlugins {..} =
9393
SMethod_TextDocumentDocumentSymbol -> ["symbolsOn" A..= plcSymbolsOn]
9494
SMethod_TextDocumentCompletion -> ["completionOn" A..= plcCompletionOn]
9595
SMethod_TextDocumentPrepareCallHierarchy -> ["callHierarchyOn" A..= plcCallHierarchyOn]
96+
SMethod_TextDocumentSemanticTokensFull -> ["semanticTokensOn" A..= plcSemanticTokensOn]
9697
_ -> []
9798

9899
-- | Generates json schema used in haskell vscode extension
@@ -123,6 +124,7 @@ pluginsToVSCodeExtensionSchema IdePlugins {..} = A.object $ mconcat $ singlePlug
123124
SMethod_TextDocumentDocumentSymbol -> [toKey' "symbolsOn" A..= schemaEntry "symbols"]
124125
SMethod_TextDocumentCompletion -> [toKey' "completionOn" A..= schemaEntry "completions"]
125126
SMethod_TextDocumentPrepareCallHierarchy -> [toKey' "callHierarchyOn" A..= schemaEntry "call hierarchy"]
127+
SMethod_TextDocumentSemanticTokensFull -> [toKey' "semanticTokensOn" A..= schemaEntry "semantic tokens"]
126128
_ -> []
127129
schemaEntry desc =
128130
A.object

hls-plugin-api/src/Ide/Types.hs

+10-1
Original file line numberDiff line numberDiff line change
@@ -230,6 +230,7 @@ data PluginConfig =
230230
, plcRenameOn :: !Bool
231231
, plcSelectionRangeOn :: !Bool
232232
, plcFoldingRangeOn :: !Bool
233+
, plcSemanticTokensOn :: !Bool
233234
, plcConfig :: !Object
234235
} deriving (Show,Eq)
235236

@@ -246,11 +247,12 @@ instance Default PluginConfig where
246247
, plcRenameOn = True
247248
, plcSelectionRangeOn = True
248249
, plcFoldingRangeOn = True
250+
, plcSemanticTokensOn = True
249251
, plcConfig = mempty
250252
}
251253

252254
instance ToJSON PluginConfig where
253-
toJSON (PluginConfig g ch ca cl d h s c rn sr fr cfg) = r
255+
toJSON (PluginConfig g ch ca cl d h s c rn sr fr st cfg) = r
254256
where
255257
r = object [ "globalOn" .= g
256258
, "callHierarchyOn" .= ch
@@ -263,6 +265,7 @@ instance ToJSON PluginConfig where
263265
, "renameOn" .= rn
264266
, "selectionRangeOn" .= sr
265267
, "foldingRangeOn" .= fr
268+
, "semanticTokensOn" .= st
266269
, "config" .= cfg
267270
]
268271

@@ -514,6 +517,9 @@ instance PluginMethod Request Method_TextDocumentRangeFormatting where
514517
where
515518
pid = pluginId pluginDesc
516519

520+
instance PluginMethod Request Method_TextDocumentSemanticTokensFull where
521+
handlesRequest = pluginEnabledWithFeature plcSemanticTokensOn
522+
517523
instance PluginMethod Request Method_TextDocumentPrepareCallHierarchy where
518524
handlesRequest = pluginEnabledWithFeature plcCallHierarchyOn
519525

@@ -751,6 +757,9 @@ instance PluginRequestMethod Method_CallHierarchyOutgoingCalls where
751757
instance PluginRequestMethod (Method_CustomMethod m) where
752758
combineResponses _ _ _ _ (x :| _) = x
753759

760+
instance PluginRequestMethod Method_TextDocumentSemanticTokensFull where
761+
combineResponses _ _ _ _ (x :| _) = x
762+
754763
takeLefts :: [a |? b] -> [a]
755764
takeLefts = mapMaybe (\x -> [res | (InL res) <- Just x])
756765

Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
- ignore: { "within": 'test/testdata/*.hs' }

0 commit comments

Comments
 (0)