1- {-# LANGUAGE DataKinds #-}
2- {-# LANGUAGE DerivingStrategies #-}
3- {-# LANGUAGE OverloadedLabels #-}
4- {-# LANGUAGE OverloadedRecordDot #-}
5- {-# LANGUAGE OverloadedStrings #-}
6- {-# LANGUAGE RecordWildCards #-}
7- {-# LANGUAGE TemplateHaskell #-}
8- {-# LANGUAGE TypeFamilies #-}
9- {-# LANGUAGE UnicodeSyntax #-}
10- {-# LANGUAGE ImpredicativeTypes #-}
11- {-# LANGUAGE LiberalTypeSynonyms #-}
12- {-# LANGUAGE BlockArguments #-}
13- {-# LANGUAGE MultiWayIf #-}
14- {-# LANGUAGE PatternSynonyms #-}
15- {-# LANGUAGE RequiredTypeArguments #-}
16- {-# LANGUAGE ViewPatterns #-}
1+ {-# LANGUAGE BlockArguments #-}
2+ {-# LANGUAGE DataKinds #-}
3+ {-# LANGUAGE DerivingStrategies #-}
4+ {-# LANGUAGE ImpredicativeTypes #-}
5+ {-# LANGUAGE LiberalTypeSynonyms #-}
6+ {-# LANGUAGE MultiWayIf #-}
7+ {-# LANGUAGE OverloadedLabels #-}
8+ {-# LANGUAGE OverloadedRecordDot #-}
9+ {-# LANGUAGE OverloadedStrings #-}
10+ {-# LANGUAGE PatternSynonyms #-}
11+ {-# LANGUAGE QuantifiedConstraints #-}
12+ {-# LANGUAGE RecordWildCards #-}
13+ {-# LANGUAGE TemplateHaskell #-}
14+ {-# LANGUAGE TypeFamilies #-}
15+ {-# LANGUAGE UnicodeSyntax #-}
16+ {-# LANGUAGE ViewPatterns #-}
1717
1818-- |
1919-- This module provides the core functionality of the plugin.
@@ -27,20 +27,29 @@ import Control.Monad.Except (ExceptT, liftEither,
2727import Control.Monad.IO.Class (MonadIO (.. ))
2828import Control.Monad.Trans (lift )
2929import Control.Monad.Trans.Except (runExceptT )
30+ import Control.Monad.Trans.Maybe
31+ import Data.Data (Data (.. ))
32+ import Data.List
3033import qualified Data.Map.Strict as M
34+ import Data.Maybe
35+ import Data.Semigroup (First (.. ))
3136import Data.Text (Text )
3237import qualified Data.Text as T
38+ import Debug.Trace
3339import Development.IDE (Action ,
3440 GetDocMap (GetDocMap ),
3541 GetHieAst (GetHieAst ),
42+ GetParsedModuleWithComments (.. ),
3643 HieAstResult (HAR , hieAst , hieModule , refMap ),
3744 IdeResult , IdeState ,
3845 Priority (.. ),
3946 Recorder , Rules ,
4047 WithPriority ,
4148 cmapWithPrio , define ,
4249 hieKind ,
43- toNormalizedUri , GetParsedModuleWithComments (.. ), srcSpanToRange )
50+ srcSpanToRange ,
51+ toNormalizedUri ,
52+ useWithStale )
4453import Development.IDE.Core.PluginUtils (runActionE , useE ,
4554 useWithStaleE )
4655import Development.IDE.Core.Rules (toIdeResult )
@@ -50,8 +59,9 @@ import Development.IDE.Core.Shake (ShakeExtras (..),
5059 getVirtualFile )
5160import Development.IDE.GHC.Compat hiding (Warning )
5261import Development.IDE.GHC.Compat.Util (mkFastString )
62+ import GHC.Parser.Annotation
5363import Ide.Logger (logWith )
54- import Ide.Plugin.Error (PluginError (PluginInternalError ),
64+ import Ide.Plugin.Error (PluginError (PluginInternalError , PluginRuleFailed ),
5565 handleMaybe ,
5666 handleMaybeM )
5767import Ide.Plugin.SemanticTokens.Mappings
@@ -63,24 +73,18 @@ import Ide.Types
6373import qualified Language.LSP.Protocol.Lens as L
6474import Language.LSP.Protocol.Message (MessageResult ,
6575 Method (Method_TextDocumentSemanticTokensFull , Method_TextDocumentSemanticTokensFullDelta ))
66- import Language.LSP.Protocol.Types (NormalizedUri ,
76+ import Language.LSP.Protocol.Types (NormalizedUri , Range ,
6777 SemanticTokens ,
6878 fromNormalizedUri ,
6979 getUri ,
70- type (|? ) (InL , InR ), Range )
80+ type (|? ) (InL , InR ))
7181import Prelude hiding (span )
7282import qualified StmContainers.Map as STM
73- import Type.Reflection
74- ( Typeable ,
75- type (:~~: )(HRefl ),
76- pattern App ,
77- eqTypeRep ,
78- typeOf ,
79- typeRep ,
80- withTypeable )
81- import Data.Data (Data (.. ))
82- import GHC.Parser.Annotation
83- import Data.Maybe
83+ import Type.Reflection (Typeable , eqTypeRep ,
84+ pattern App ,
85+ type (:~~: ) (HRefl ),
86+ typeOf , typeRep ,
87+ withTypeable )
8488
8589
8690$ mkSemanticConfigFunctions
@@ -94,9 +98,17 @@ computeSemanticTokens recorder pid _ nuri = do
9498 config <- lift $ useSemanticConfigAction pid
9599 logWith recorder Debug (LogConfig config)
96100 semanticId <- lift getAndIncreaseSemanticTokensId
97- (RangeHsSemanticTokenTypes {rangeSemanticList}, _mapping) <- useWithStaleE GetSemanticTokens nuri
98- (RangeHsSyntacticTokenTypes {rangeSyntacticList}, mapping) <- useWithStaleE GetSyntacticTokens nuri
99- withExceptT PluginInternalError $ liftEither $ rangeSemanticsSemanticTokens semanticId config mapping $ map (fmap HsSemanticTokenType ) rangeSemanticList <> map (fmap HsSyntacticTokenType ) rangeSyntacticList
101+
102+ (sortOn fst -> tokenList, First mapping) <- do
103+ rangesyntacticTypes <- lift $ useWithStale GetSyntacticTokens nuri
104+ rangesemanticTypes <- lift $ useWithStale GetSemanticTokens nuri
105+ let mk w u (toks, mapping) = (map (fmap w) $ u toks, First mapping)
106+ maybeToExceptT (PluginRuleFailed " no syntactic nor semantic tokens" ) $ hoistMaybe $
107+ (mk HsSyntacticTokenType rangeSyntacticList <$> rangesyntacticTypes)
108+ <> (mk HsSemanticTokenType rangeSemanticList <$> rangesemanticTypes)
109+
110+ -- NOTE: rangeSemanticsSemanticTokens actually assumes that the tokesn are in order. that means they have to be sorted by position
111+ withExceptT PluginInternalError $ liftEither $ rangeSemanticsSemanticTokens semanticId config mapping tokenList
100112
101113semanticTokensFull :: Recorder (WithPriority SemanticLog ) -> PluginMethodHandler IdeState 'Method_TextDocumentSemanticTokensFull
102114semanticTokensFull recorder state pid param = runActionE " SemanticTokens.semanticTokensFull" state computeSemanticTokensFull
@@ -153,35 +165,85 @@ getSemanticTokensRule recorder =
153165getSyntacticTokensRule :: Recorder (WithPriority SemanticLog ) -> Rules ()
154166getSyntacticTokensRule recorder =
155167 define (cmapWithPrio LogShake recorder) $ \ GetSyntacticTokens nfp -> handleError recorder $ do
156- (parsedModule, positionMapping ) <- withExceptT LogDependencyError $ useWithStaleE GetParsedModuleWithComments nfp
157- pure $ computeRangeHsSyntacticTokenTypeList parsedModule
158-
159- getLocated's :: forall l a . ( Data a , Typeable l ) => a -> [ GenLocated l ( forall r . ( forall b . Typeable b => b -> r ) -> r )]
160- getLocated's = mconcat . gmapQ \ y -> if
161- | App con rep <- typeOf y
162- , Just HRefl <- eqTypeRep con (typeRep @ ( GenLocated l ))
163- , L l a <- y
164- -> withTypeable rep $ L l ( \ k -> k a) : getLocated's y
165- | otherwise -> getLocated's y
166-
167- pattern IsA :: forall b t . ( Typeable b , Typeable t ) => forall . b ~ t => b -> t
168- pattern IsA x <- (( \ y -> (y, eqTypeRep (typeRep @ b ) (typeOf y))) -> (x, Just HRefl ) )
169-
170- mkFromLocatedNode :: GenLocated SrcSpanAnnA ( forall r . ( forall b . Typeable b => b -> r ) -> r ) -> Maybe ( Range , HsSyntacticTokenType )
171- mkFromLocatedNode ( L ann w) = w \ node -> case node of
172- IsA @ ( HsExpr GhcPs ) expr -> case expr of
173- HsLet {} -> let
174- mrange = srcSpanToRange $ getLoc ann
175- in (, TKeyword ) <$> mrange
176- _ -> Nothing
177- _ -> Nothing
168+ (parsedModule, _ ) <- withExceptT LogDependencyError $ useWithStaleE GetParsedModuleWithComments nfp
169+ let tokList = computeRangeHsSyntacticTokenTypeList parsedModule
170+ logWith recorder Debug $ LogSyntacticTokens tokList
171+ pure tokList
172+
173+ astTraversalWith :: forall b r . Data b => b -> ( forall a . Data a => a -> [ r ]) -> [ r ]
174+ astTraversalWith ast f = mconcat $ flip gmapQ ast \ y -> f y <> astTraversalWith y f
175+
176+ {-# inline extractTyToTy #-}
177+ extractTyToTy :: forall f a . ( Typeable f , Data a ) => a -> Maybe ( forall r . ( forall b . Typeable b => f b -> r ) -> r )
178+ extractTyToTy node
179+ | App conRep argRep <- typeOf node
180+ , Just HRefl <- eqTypeRep conRep (typeRep @ f )
181+ = Just $ withTypeable argRep $ ( \ k -> k node)
182+ | otherwise = Nothing
183+
184+ {-# inline extractTy #-}
185+ extractTy :: forall b a . ( Typeable b , Data a ) => a -> Maybe b
186+ extractTy node
187+ | Just HRefl <- eqTypeRep (typeRep @ b ) (typeOf node)
188+ = Just node
189+ | otherwise = Nothing
178190
179191computeRangeHsSyntacticTokenTypeList :: ParsedModule -> RangeHsSyntacticTokenTypes
180192computeRangeHsSyntacticTokenTypeList ParsedModule {pm_parsed_source} =
181- let locs = getLocated's @ SrcSpanAnnA pm_parsed_source
182- toks = mapMaybe mkFromLocatedNode locs
193+ let toks = astTraversalWith pm_parsed_source \ node -> mconcat
194+ [ maybeToList $ mkFromLocatable TKeyword . (\ k -> k \ x k' -> k' x) =<< extractTyToTy @ EpToken node
195+ -- FIXME: probably needs to be commented out for ghc > 9.10
196+ , maybeToList $ mkFromLocatable TKeyword . (\ x k -> k x) =<< extractTy @ AddEpAnn node
197+ , do
198+ EpAnnImportDecl i p s q pkg a <- maybeToList $ extractTy @ EpAnnImportDecl node
199+
200+ mapMaybe (mkFromLocatable TKeyword . (\ x k -> k x)) $ catMaybes $ [Just i, s, q, pkg, a] <> foldMap (\ (l, l') -> [Just l, Just l']) p
201+ , maybeToList $ mkFromLocatable TComment . (\ x k -> k x) =<< extractTy @ LEpaComment node
202+ , do
203+ L loc expr <- maybeToList $ extractTy @ (LHsExpr GhcPs ) node
204+ let fromSimple = maybeToList . flip mkFromLocatable \ k -> k loc
205+ case expr of
206+ HsOverLabel {} -> fromSimple TStringLit
207+ HsOverLit _ (OverLit _ lit) -> fromSimple case lit of
208+ HsIntegral {} -> TNumberLit
209+ HsFractional {} -> TNumberLit
210+
211+ HsIsString {} -> TStringLit
212+ HsLit _ lit -> fromSimple case lit of
213+ HsChar {} -> TCharLit
214+ HsCharPrim {} -> TCharLit
215+
216+ HsInt {} -> TNumberLit
217+ HsInteger {} -> TNumberLit
218+ HsIntPrim {} -> TNumberLit
219+ HsWordPrim {} -> TNumberLit
220+ HsWord8Prim {} -> TNumberLit
221+ HsWord16Prim {} -> TNumberLit
222+ HsWord32Prim {} -> TNumberLit
223+ HsWord64Prim {} -> TNumberLit
224+ HsInt8Prim {} -> TNumberLit
225+ HsInt16Prim {} -> TNumberLit
226+ HsInt32Prim {} -> TNumberLit
227+ HsInt64Prim {} -> TNumberLit
228+ HsFloatPrim {} -> TNumberLit
229+ HsDoublePrim {} -> TNumberLit
230+ HsRat {} -> TNumberLit
231+
232+ HsString {} -> TStringLit
233+ HsStringPrim {} -> TStringLit
234+ HsGetField _ _ field -> trace " ============== HIT RECORD SELECTOR" $ maybeToList $ mkFromLocatable TRecordSelector \ k -> k field
235+ HsProjection _ projs -> trace " ============== HIT RECORD SELECTOR" $ foldMap (\ proj -> maybeToList $ mkFromLocatable TRecordSelector \ k -> k proj) projs
236+ _ -> []
237+ ]
183238 in RangeHsSyntacticTokenTypes toks
184239
240+ {-# inline mkFromLocatable #-}
241+ mkFromLocatable
242+ :: HsSyntacticTokenType
243+ -> (forall r . (forall a . HasSrcSpan a => a -> r ) -> r )
244+ -> Maybe (Range , HsSyntacticTokenType )
245+ mkFromLocatable tt w = w \ tok -> let mrange = srcSpanToRange $ getLoc tok in fmap (, tt) mrange
246+
185247-- taken from /haskell-language-server/plugins/hls-code-range-plugin/src/Ide/Plugin/CodeRange/Rules.hs
186248
187249-- | Handle error in 'Action'. Returns an 'IdeResult' with no value and no diagnostics on error. (but writes log)
0 commit comments