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 (..))
3332import Data.List
3433import qualified Data.Map.Strict as M
3534import Data.Maybe
36- import Data.Semigroup (First (.. ))
3735import Data.Text (Text )
3836import qualified Data.Text as T
3937import Development.IDE (Action ,
@@ -51,6 +49,7 @@ import Development.IDE (Action,
5149 useWithStale )
5250import Development.IDE.Core.PluginUtils (runActionE , useE ,
5351 useWithStaleE )
52+ import Development.IDE.Core.PositionMapping
5453import Development.IDE.Core.Rules (toIdeResult )
5554import Development.IDE.Core.RuleTypes (DocAndTyThingMap (.. ))
5655import 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
115114semanticTokensFull :: Recorder (WithPriority SemanticLog ) -> PluginMethodHandler IdeState 'Method_TextDocumentSemanticTokensFull
116115semanticTokensFull recorder state pid param = runActionE " SemanticTokens.semanticTokensFull" state computeSemanticTokensFull
@@ -168,9 +167,7 @@ getSyntacticTokensRule :: Recorder (WithPriority SemanticLog) -> Rules ()
168167getSyntacticTokensRule 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
175172astTraversalWith :: forall b r . Data b => b -> (forall a . Data a => a -> [r ]) -> [r ]
176173astTraversalWith ast f = mconcat $ flip gmapQ ast \ y -> f y <> astTraversalWith y f
0 commit comments