Skip to content

Commit 3488155

Browse files
committed
add realSrcSpanToCodePointRange, realSrcLocToCodePointPosition to Development.IDE.GHC.Error, to put them beside realSrcSpanToRange, realSrcLocToPosition
1 parent 71e6532 commit 3488155

File tree

4 files changed

+5
-14
lines changed

4 files changed

+5
-14
lines changed

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

+1-1
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ semanticTokensFull state _ param = do
9494
-- Visible names from 'tmrRenamed'
9595
--
9696
-- It then combines this information to compute the semantic tokens for the file.
97-
getSemanticTokensRule :: Recorder (WithPriority SemanticLog) -> Rules ()
97+
getSemanticTokensRule :: Recorder (WithPriority SemanticLog) -> Rules ()
9898
getSemanticTokensRule recorder =
9999
define (cmapWithPrio LogShake recorder) $ \GetSemanticTokens nfp -> handleError recorder $ do
100100
(HAR {..}) <- lift $ use_ GetHieAst nfp

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

+1-1
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ import qualified Data.Set as Set
2020
import Data.Text (Text, unpack)
2121
import Development.IDE (HieKind (HieFresh, HieFromDisk))
2222
import Development.IDE.GHC.Compat
23-
import Ide.Plugin.SemanticTokens.Types hiding (tokens)
23+
import Ide.Plugin.SemanticTokens.Types
2424
import Ide.Plugin.SemanticTokens.Utils (mkRange, recoverFunMaskArray)
2525
import Language.LSP.Protocol.Types (LspEnum (knownValues),
2626
SemanticTokenAbsolute (SemanticTokenAbsolute),

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

+3-1
Original file line numberDiff line numberDiff line change
@@ -19,11 +19,11 @@ import Data.Text (Text)
1919
import Development.IDE.Core.PositionMapping (PositionMapping,
2020
toCurrentRange)
2121
import Development.IDE.GHC.Compat
22+
import Development.IDE.GHC.Error (realSrcSpanToCodePointRange)
2223
import Ide.Plugin.SemanticTokens.Mappings
2324
import Ide.Plugin.SemanticTokens.Types (HieFunMaskKind,
2425
HsSemanticTokenType,
2526
NameSemanticMap)
26-
import Ide.Plugin.SemanticTokens.Utils (realSrcSpanToCodePointRange)
2727
import Language.LSP.Protocol.Types
2828
import Language.LSP.VFS (VirtualFile,
2929
codePointRangeToRange)
@@ -50,6 +50,8 @@ nameNameSemanticFromHie hieKind rm ns = do
5050
nameSemanticFromRefMap rm' name' = do
5151
spanInfos <- -- traceShow ("getting spans:", nameString) $
5252
Map.lookup (Right name') rm'
53+
-- let combinedFunction x = (identType . snd) x <|> (identInfo . snd) x
54+
-- let result = foldMap (typeSemantic hieKind) $ listToMaybe $ mapMaybe combinedFunction spanInfos
5355
let typeTokenType = foldMap (typeSemantic hieKind) $ listToMaybe $ mapMaybe (identType . snd) spanInfos
5456
contextInfoTokenType <- foldMap (contextInfosMaybeTokenType . identInfo . snd) spanInfos
5557
fold [typeTokenType, Just contextInfoTokenType]

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

-11
Original file line numberDiff line numberDiff line change
@@ -123,18 +123,7 @@ recoverFunMaskArray flattened = unflattened
123123
go (HTyConApp _ _) = False
124124

125125

126-
realSrcSpanToCodePointRange :: RealSrcSpan -> CodePointRange
127-
realSrcSpanToCodePointRange real =
128-
CodePointRange (realSrcLocToCodePointPosition $ Compat.realSrcSpanStart real)
129-
(realSrcLocToCodePointPosition $ Compat.realSrcSpanEnd real)
130-
131-
132-
realSrcLocToCodePointPosition :: RealSrcLoc -> CodePointPosition
133-
realSrcLocToCodePointPosition real =
134-
CodePointPosition (fromIntegral $ srcLocLine real - 1) (fromIntegral $ srcLocCol real - 1)
135-
136126
-- rangeToCodePointRange
137-
-- mkRange :: Int -> Int -> Int -> Range
138127
mkRange :: (Integral a1, Integral a2) => a1 -> a2 -> a2 -> Range
139128
mkRange startLine startCol len =
140129
Range (Position (fromIntegral startLine) (fromIntegral startCol)) (Position (fromIntegral startLine) (fromIntegral $ startCol + len))

0 commit comments

Comments
 (0)