Skip to content

Commit ea277ac

Browse files
committed
[fix] apply mappings per set of syntactic vs semantic tokens
1 parent 457d477 commit ea277ac

File tree

4 files changed

+11
-13
lines changed

4 files changed

+11
-13
lines changed

plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Internal.hs

Lines changed: 5 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,6 @@
1414
{-# LANGUAGE TemplateHaskell #-}
1515
{-# LANGUAGE TypeFamilies #-}
1616
{-# LANGUAGE UnicodeSyntax #-}
17-
{-# LANGUAGE ViewPatterns #-}
1817

1918
-- |
2019
-- This module provides the core functionality of the plugin.
@@ -33,7 +32,6 @@ import Data.Data (Data (..))
3332
import Data.List
3433
import qualified Data.Map.Strict as M
3534
import Data.Maybe
36-
import Data.Semigroup (First (..))
3735
import Data.Text (Text)
3836
import qualified Data.Text as T
3937
import Development.IDE (Action,
@@ -51,6 +49,7 @@ import Development.IDE (Action,
5149
useWithStale)
5250
import Development.IDE.Core.PluginUtils (runActionE, useE,
5351
useWithStaleE)
52+
import Development.IDE.Core.PositionMapping
5453
import Development.IDE.Core.Rules (toIdeResult)
5554
import Development.IDE.Core.RuleTypes (DocAndTyThingMap (..))
5655
import Development.IDE.Core.Shake (ShakeExtras (..),
@@ -101,16 +100,16 @@ computeSemanticTokens recorder pid _ nfp = do
101100
logWith recorder Debug (LogConfig config)
102101
semanticId <- lift getAndIncreaseSemanticTokensId
103102

104-
(sortOn fst -> tokenList, First mapping) <- do
103+
tokenList <- sortOn fst <$> do
105104
rangesyntacticTypes <- lift $ useWithStale GetSyntacticTokens nfp
106105
rangesemanticTypes <- lift $ useWithStale GetSemanticTokens nfp
107-
let mk w u (toks, mapping) = (map (fmap w) $ u toks, First mapping)
106+
let mk w u (toks, mapping) = map (\(ran, tok) -> (toCurrentRange mapping ran, w tok)) $ u toks
108107
maybeToExceptT (PluginRuleFailed "no syntactic nor semantic tokens") $ hoistMaybe $
109108
(mk HsSyntacticTokenType rangeSyntacticList <$> rangesyntacticTypes)
110109
<> (mk HsSemanticTokenType rangeSemanticList <$> rangesemanticTypes)
111110

112111
-- NOTE: rangeSemanticsSemanticTokens actually assumes that the tokesn are in order. that means they have to be sorted by position
113-
withExceptT PluginInternalError $ liftEither $ rangeSemanticsSemanticTokens semanticId config mapping tokenList
112+
withExceptT PluginInternalError $ liftEither $ rangeSemanticsSemanticTokens semanticId config tokenList
114113

115114
semanticTokensFull :: Recorder (WithPriority SemanticLog) -> PluginMethodHandler IdeState 'Method_TextDocumentSemanticTokensFull
116115
semanticTokensFull recorder state pid param = runActionE "SemanticTokens.semanticTokensFull" state computeSemanticTokensFull
@@ -168,9 +167,7 @@ getSyntacticTokensRule :: Recorder (WithPriority SemanticLog) -> Rules ()
168167
getSyntacticTokensRule recorder =
169168
define (cmapWithPrio LogShake recorder) $ \GetSyntacticTokens nfp -> handleError recorder $ do
170169
(parsedModule, _) <- withExceptT LogDependencyError $ useWithStaleE GetParsedModuleWithComments nfp
171-
let tokList = computeRangeHsSyntacticTokenTypeList parsedModule
172-
logWith recorder Debug $ LogSyntacticTokens tokList
173-
pure tokList
170+
pure $ computeRangeHsSyntacticTokenTypeList parsedModule
174171

175172
astTraversalWith :: forall b r. Data b => b -> (forall a. Data a => a -> [r]) -> [r]
176173
astTraversalWith ast f = mconcat $ flip gmapQ ast \y -> f y <> astTraversalWith y f

plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Query.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -70,9 +70,9 @@ nameSemanticFromHie hieKind rm n = idSemanticFromRefMap rm (Right n)
7070

7171
-------------------------------------------------
7272

73-
rangeSemanticsSemanticTokens :: SemanticTokenId -> SemanticTokensConfig -> PositionMapping -> [(Range, HsTokenType)] -> Either Text SemanticTokens
74-
rangeSemanticsSemanticTokens sid stc mapping =
75-
makeSemanticTokensWithId (Just sid) . mapMaybe (\(ran, tk) -> toAbsSemanticToken <$> toCurrentRange mapping ran <*> return tk)
73+
rangeSemanticsSemanticTokens :: SemanticTokenId -> SemanticTokensConfig -> [(Maybe Range, HsTokenType)] -> Either Text SemanticTokens
74+
rangeSemanticsSemanticTokens sid stc =
75+
makeSemanticTokensWithId (Just sid) . mapMaybe (\(ran, tk) -> toAbsSemanticToken <$> ran <*> return tk)
7676
where
7777
toAbsSemanticToken :: Range -> HsTokenType -> SemanticTokenAbsolute
7878
toAbsSemanticToken (Range (Position startLine startColumn) (Position _endLine endColumn)) tokenType =

plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/SemanticConfig.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,9 @@ docName tt = case tt of
4444
HsSyntacticTokenType TKeyword -> "keyword"
4545
HsSyntacticTokenType TStringLit -> "string literal"
4646
HsSyntacticTokenType TComment -> "comment"
47+
HsSyntacticTokenType TCharLit -> "char literal"
48+
HsSyntacticTokenType TNumberLit -> "number literal"
49+
HsSyntacticTokenType TRecordSelector -> "record selector"
4750

4851
toConfigName :: String -> String
4952
toConfigName = ("st" <>)

plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Types.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -181,7 +181,6 @@ data SemanticLog
181181
| LogConfig SemanticTokensConfig
182182
| LogMsg String
183183
| LogNoVF
184-
| LogSyntacticTokens RangeHsSyntacticTokenTypes
185184
| LogSemanticTokensDeltaMisMatch Text (Maybe Text)
186185

187186
instance Pretty SemanticLog where
@@ -195,6 +194,5 @@ instance Pretty SemanticLog where
195194
-> "SemanticTokensDeltaMisMatch: previousIdFromRequest: " <> pretty previousIdFromRequest
196195
<> " previousIdFromCache: " <> pretty previousIdFromCache
197196
LogDependencyError err -> "SemanticTokens' dependency error: " <> pretty err
198-
LogSyntacticTokens (RangeHsSyntacticTokenTypes synList) -> "Syntactic tokens: " <> pretty (show synList)
199197

200198
type SemanticTokenId = Text

0 commit comments

Comments
 (0)