55{-# LANGUAGE RankNTypes #-}
66{-# LANGUAGE ScopedTypeVariables #-}
77
8-
98module Ide.Plugin.SemanticTokens.Query where
109
11- import Data.Either (rights )
12- import Data.Foldable (fold )
13- import qualified Data.List as List
14- import qualified Data.Map as M
15- import qualified Data.Map as Map
16- import Data.Maybe ( fromMaybe , listToMaybe ,
17- mapMaybe )
18- import qualified Data.Set as S
19- import qualified Data.Set as Set
20- import Data.Text ( Text )
21- import Development.IDE ( realSrcSpanToRange )
10+ import Data.Either (rights )
11+ import Data.Foldable (fold )
12+ import qualified Data.Map as M
13+ import qualified Data.Map as Map
14+ import Data.Maybe ( fromMaybe , listToMaybe ,
15+ mapMaybe )
16+ import qualified Data.Set as S
17+ import qualified Data.Set as Set
18+ import Data.Text ( Text )
19+ import Development.IDE.Core.PositionMapping ( PositionMapping ,
20+ toCurrentRange )
2221import Development.IDE.GHC.Compat
2322import Ide.Plugin.SemanticTokens.Mappings
24- import Ide.Plugin.SemanticTokens.Types (HieFunMaskKind ,
25- HsSemanticTokenType ,
26- NameSemanticMap )
27- import Ide.Plugin.SemanticTokens.Utils (realSrcSpanToCodePointRange )
23+ import Ide.Plugin.SemanticTokens.Types (HieFunMaskKind ,
24+ HsSemanticTokenType ,
25+ NameSemanticMap )
26+ import Ide.Plugin.SemanticTokens.Utils (realSrcSpanToCodePointRange )
2827import Language.LSP.Protocol.Types
29- import Language.LSP.VFS (CodePointRange ,
30- VirtualFile ,
31- codePointRangeToRange )
32- import Prelude hiding (span )
28+ import Language.LSP.VFS (VirtualFile ,
29+ codePointRangeToRange )
30+ import Prelude hiding (span )
3331
3432---------------------------------------------------------
3533
@@ -74,9 +72,9 @@ hieAstSpanNames vf ast =
7472 then getIds ast
7573 else M. unionsWith unionNameSet $ map (hieAstSpanNames vf) (nodeChildren ast)
7674 where
77- getIds ast' = fromMaybe mempty $ do
78- range <- codePointRangeToRange vf $ realSrcSpanToCodePointRange $ nodeSpan ast'
79- return $ M. singleton range (getNodeIds' ast')
75+ getIds ast' = fromMaybe mempty $ do
76+ range <- codePointRangeToRange vf $ realSrcSpanToCodePointRange $ nodeSpan ast'
77+ return $ M. singleton range (getNodeIds' ast')
8078 getNodeIds' =
8179 Map. foldl' combineNodeIds mempty
8280 . Map. filterWithKey (\ k _ -> k == SourceInfo )
@@ -85,25 +83,32 @@ hieAstSpanNames vf ast =
8583 combineNodeIds :: NameSet -> NodeInfo a -> NameSet
8684 ad `combineNodeIds` (NodeInfo _ _ bd) = ad `unionNameSet` xs
8785 where
88- xs = mkNameSet $ rights $ M. keys $ M. filterWithKey inclusion bd
86+ xs = mkNameSet $ rights $ M. keys $ M. filterWithKey inclusion bd
8987 inclusion :: Identifier -> IdentifierDetails a -> Bool
9088 inclusion a b = not $ exclusion a b
9189 exclusion :: Identifier -> IdentifierDetails a -> Bool
9290 exclusion idt IdentifierDetails {identInfo = infos} = case idt of
93- Left _ -> True
94- Right name ->
95- isDerivedOccName (nameOccName name)
96- || any isEvidenceContext (S. toList infos)
97-
91+ Left _ -> True
92+ Right name ->
93+ isDerivedOccName (nameOccName name)
94+ || any isEvidenceContext (S. toList infos)
9895
9996-------------------------------------------------
10097
10198-- * extract semantic tokens from NameSemanticMap
10299
103100-------------------------------------------------
104101
105- semanticTokenAbsoluteSemanticTokens :: [(Range , HsSemanticTokenType )] -> Either Text SemanticTokens
106- semanticTokenAbsoluteSemanticTokens = makeSemanticTokens defaultSemanticTokensLegend . List. sort . map (uncurry toAbsSemanticToken)
102+ extractSemanticTokensFromNames :: NameSemanticMap -> M. Map Range NameSet -> M. Map Range HsSemanticTokenType
103+ extractSemanticTokensFromNames nsm rnMap = Map. mapMaybe (foldMap (lookupNameEnv nsm) . nameSetElemsStable) rnMap
104+
105+
106+ rangeSemanticMapSemanticTokens :: PositionMapping -> M. Map Range HsSemanticTokenType -> Either Text SemanticTokens
107+ rangeSemanticMapSemanticTokens mapping =
108+ makeSemanticTokens defaultSemanticTokensLegend
109+ . mapMaybe (\ (range, ty) -> flip toAbsSemanticToken ty <$> range)
110+ . Map. toAscList
111+ . M. mapKeys (\ r -> toCurrentRange mapping r)
107112 where
108113 toAbsSemanticToken :: Range -> HsSemanticTokenType -> SemanticTokenAbsolute
109114 toAbsSemanticToken (Range (Position startLine startColumn) (Position _endLine endColumn)) tokenType =
@@ -114,7 +119,3 @@ semanticTokenAbsoluteSemanticTokens = makeSemanticTokens defaultSemanticTokensLe
114119 (fromIntegral len)
115120 (toLspTokenType tokenType)
116121 []
117-
118- extractSemanticTokensFromNames :: NameSemanticMap -> M. Map Range NameSet -> [(Range , HsSemanticTokenType )]
119- extractSemanticTokensFromNames nsm rnMap = xs
120- where xs = mapMaybe sequence (Map. toList $ Map. map (foldMap (lookupNameEnv nsm) . nameSetElemsStable) rnMap)
0 commit comments