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       #-}
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          #-}
1017
1118--  | 
1219--  This module provides the core functionality of the plugin. 
@@ -20,20 +27,28 @@ import           Control.Monad.Except                     (ExceptT, liftEither,
2027import            Control.Monad.IO.Class                    (MonadIO  (.. ))
2128import            Control.Monad.Trans                       (lift )
2229import            Control.Monad.Trans.Except                (runExceptT )
30+ import            Control.Monad.Trans.Maybe 
31+ import            Data.Data                                 (Data  (.. ))
32+ import            Data.List 
2333import  qualified  Data.Map.Strict                           as  M 
34+ import            Data.Maybe 
35+ import            Data.Semigroup                            (First  (.. ))
2436import            Data.Text                                 (Text )
2537import  qualified  Data.Text                                 as  T 
2638import            Development.IDE                           (Action ,
2739                                                           GetDocMap  (GetDocMap ),
2840                                                           GetHieAst  (GetHieAst ),
41+                                                            GetParsedModuleWithComments  (.. ),
2942                                                           HieAstResult  (HAR , hieAst , hieModule , refMap ),
3043                                                           IdeResult , IdeState ,
3144                                                           Priority  (.. ),
3245                                                           Recorder , Rules ,
3346                                                           WithPriority ,
3447                                                           cmapWithPrio , define ,
35-                                                            fromNormalizedFilePath ,
36-                                                            hieKind )
48+                                                            hieKind ,
49+                                                            srcSpanToRange ,
50+                                                            toNormalizedUri ,
51+                                                            useWithStale )
3752import            Development.IDE.Core.PluginUtils          (runActionE , useE ,
3853                                                           useWithStaleE )
3954import            Development.IDE.Core.Rules                (toIdeResult )
@@ -43,9 +58,9 @@ import           Development.IDE.Core.Shake               (ShakeExtras (..),
4358                                                           getVirtualFile )
4459import            Development.IDE.GHC.Compat                hiding  (Warning )
4560import            Development.IDE.GHC.Compat.Util           (mkFastString )
61+ import            GHC.Parser.Annotation 
4662import            Ide.Logger                                (logWith )
47- import            Ide.Plugin.Error                          (PluginError  (PluginInternalError ),
48-                                                            getNormalizedFilePathE ,
63+ import            Ide.Plugin.Error                          (PluginError  (PluginInternalError , PluginRuleFailed ),
4964                                                           handleMaybe ,
5065                                                           handleMaybeM )
5166import            Ide.Plugin.SemanticTokens.Mappings 
@@ -57,11 +72,18 @@ import           Ide.Types
5772import  qualified  Language.LSP.Protocol.Lens                as  L 
5873import            Language.LSP.Protocol.Message             (MessageResult ,
5974                                                           Method  (Method_TextDocumentSemanticTokensFull , Method_TextDocumentSemanticTokensFullDelta ))
60- import            Language.LSP.Protocol.Types               (NormalizedFilePath ,
75+ import            Language.LSP.Protocol.Types               (NormalizedUri ,  Range ,
6176                                                           SemanticTokens ,
77+                                                            fromNormalizedUri ,
78+                                                            getUri ,
6279                                                           type  (|? ) (InL , InR ))
6380import            Prelude                                   hiding  (span )
6481import  qualified  StmContainers.Map                         as  STM 
82+ import            Type.Reflection                           (Typeable , eqTypeRep ,
83+                                                            pattern  App ,
84+                                                            type  (:~~: ) (HRefl ),
85+                                                            typeOf , typeRep ,
86+                                                            withTypeable )
6587
6688
6789$ 
@@ -75,8 +97,17 @@ computeSemanticTokens recorder pid _ nfp = do
7597  config <-  lift $  useSemanticConfigAction pid
7698  logWith recorder Debug  (LogConfig  config)
7799  semanticId <-  lift getAndIncreaseSemanticTokensId
78-   (RangeHsSemanticTokenTypes  {rangeSemanticList}, mapping) <-  useWithStaleE GetSemanticTokens  nfp
79-   withExceptT PluginInternalError  $  liftEither $  rangeSemanticsSemanticTokens semanticId config mapping rangeSemanticList
100+ 
101+   (sortOn fst  ->  tokenList, First  mapping) <-  do 
102+     rangesyntacticTypes <-  lift $  useWithStale GetSyntacticTokens  nuri
103+     rangesemanticTypes <-  lift $  useWithStale GetSemanticTokens  nuri
104+     let  mk w u (toks, mapping) =  (map  (fmap  w) $  u toks, First  mapping)
105+     maybeToExceptT (PluginRuleFailed  " no syntactic nor semantic tokens" $  hoistMaybe $ 
106+       (mk HsSyntacticTokenType  rangeSyntacticList <$>  rangesyntacticTypes)
107+       <>   (mk HsSemanticTokenType  rangeSemanticList <$>  rangesemanticTypes)
108+ 
109+   --  NOTE: rangeSemanticsSemanticTokens actually assumes that the tokesn are in order. that means they have to be sorted by position
110+   withExceptT PluginInternalError  $  liftEither $  rangeSemanticsSemanticTokens semanticId config mapping tokenList
80111
81112semanticTokensFull  ::  Recorder  (WithPriority  SemanticLog ) ->  PluginMethodHandler  IdeState  'Method_TextDocumentSemanticTokensFull
82113semanticTokensFull recorder state pid param =  runActionE " SemanticTokens.semanticTokensFull" 
@@ -130,6 +161,87 @@ getSemanticTokensRule recorder =
130161    let  hsFinder =  idSemantic getTyThingMap (hieKindFunMasksKind hieKind) refMap
131162    return  $  computeRangeHsSemanticTokenTypeList hsFinder virtualFile ast
132163
164+ getSyntacticTokensRule  ::  Recorder  (WithPriority  SemanticLog ) ->  Rules  () 
165+ getSyntacticTokensRule recorder = 
166+   define (cmapWithPrio LogShake  recorder) $  \ GetSyntacticTokens  nfp ->  handleError recorder $  do 
167+     (parsedModule, _) <-  withExceptT LogDependencyError  $  useWithStaleE GetParsedModuleWithComments  nfp
168+     let  tokList =  computeRangeHsSyntacticTokenTypeList parsedModule
169+     logWith recorder Debug  $  LogSyntacticTokens  tokList
170+     pure  tokList
171+ 
172+ astTraversalWith  ::  forall  b  r .  Data  b  =>  b  ->  (forall  a .  Data  a  =>  a  ->  [r ]) ->  [r ]
173+ astTraversalWith ast f =  mconcat  $  flip  gmapQ ast \ y ->  f y <>  astTraversalWith y f
174+ 
175+ {-# inline  extractTyToTy #-}
176+ extractTyToTy  ::  forall  f  a .  (Typeable  f , Data  a ) =>  a  ->  Maybe forall  r .  (forall  b .  Typeable  b  =>  f  b  ->  r ) ->  r )
177+ extractTyToTy node
178+   |  App  conRep argRep <-  typeOf node
179+   , Just  HRefl  <-  eqTypeRep conRep (typeRep @ f )
180+   =  Just  $  withTypeable argRep $  (\ k ->  k node)
181+   |  otherwise  =  Nothing 
182+ 
183+ {-# inline  extractTy #-}
184+ extractTy  ::  forall  b  a .  (Typeable  b , Data  a ) =>  a  ->  Maybe b 
185+ extractTy node
186+   |  Just  HRefl  <-  eqTypeRep (typeRep @ b ) (typeOf node)
187+   =  Just  node
188+   |  otherwise  =  Nothing 
189+ 
190+ computeRangeHsSyntacticTokenTypeList  ::  ParsedModule  ->  RangeHsSyntacticTokenTypes 
191+ computeRangeHsSyntacticTokenTypeList ParsedModule  {pm_parsed_source} = 
192+   let  toks =  astTraversalWith pm_parsed_source \ node ->  mconcat 
193+          [ maybeToList $  mkFromLocatable TKeyword  .  (\ k ->  k \ x k' ->  k' x) =<<  extractTyToTy @ EpToken  node
194+          --  FIXME: probably needs to be commented out for ghc > 9.10
195+          , maybeToList $  mkFromLocatable TKeyword  .  (\ x k ->  k x) =<<  extractTy @ AddEpAnn  node
196+          , do 
197+            EpAnnImportDecl  i p s q pkg a <-  maybeToList $  extractTy @ EpAnnImportDecl  node
198+ 
199+            mapMaybe (mkFromLocatable TKeyword  .  (\ x k ->  k x)) $  catMaybes $  [Just  i, s, q, pkg, a] <>  foldMap  (\ (l, l') ->  [Just  l, Just  l']) p
200+          , maybeToList $  mkFromLocatable TComment  .  (\ x k ->  k x) =<<  extractTy @ LEpaComment  node
201+          , do 
202+            L  loc expr <-  maybeToList $  extractTy @ (LHsExpr  GhcPs ) node
203+            let  fromSimple =  maybeToList .  flip  mkFromLocatable \ k ->  k loc
204+            case  expr of 
205+              HsOverLabel  {} ->  fromSimple TStringLit 
206+              HsOverLit  _ (OverLit  _ lit) ->  fromSimple case  lit of 
207+                HsIntegral  {}   ->  TNumberLit 
208+                HsFractional  {} ->  TNumberLit 
209+ 
210+                HsIsString  {}   ->  TStringLit 
211+              HsLit  _ lit ->  fromSimple case  lit of 
212+                  HsChar  {}       ->  TCharLit 
213+                  HsCharPrim  {}   ->  TCharLit 
214+ 
215+                  HsInt  {}        ->  TNumberLit 
216+                  HsInteger  {}    ->  TNumberLit 
217+                  HsIntPrim  {}    ->  TNumberLit 
218+                  HsWordPrim  {}   ->  TNumberLit 
219+                  HsWord8Prim  {}  ->  TNumberLit 
220+                  HsWord16Prim  {} ->  TNumberLit 
221+                  HsWord32Prim  {} ->  TNumberLit 
222+                  HsWord64Prim  {} ->  TNumberLit 
223+                  HsInt8Prim  {}   ->  TNumberLit 
224+                  HsInt16Prim  {}  ->  TNumberLit 
225+                  HsInt32Prim  {}  ->  TNumberLit 
226+                  HsInt64Prim  {}  ->  TNumberLit 
227+                  HsFloatPrim  {}  ->  TNumberLit 
228+                  HsDoublePrim  {} ->  TNumberLit 
229+                  HsRat  {}        ->  TNumberLit 
230+ 
231+                  HsString  {}     ->  TStringLit 
232+                  HsStringPrim  {} ->  TStringLit 
233+              HsGetField  _ _ field ->  maybeToList $  mkFromLocatable TRecordSelector  \ k ->  k field
234+              HsProjection  _ projs ->  foldMap  (\ proj ->  maybeToList $  mkFromLocatable TRecordSelector  \ k ->  k proj) projs
235+              _ ->  [] 
236+          ]
237+    in  RangeHsSyntacticTokenTypes  toks
238+ 
239+ {-# inline  mkFromLocatable #-}
240+ mkFromLocatable
241+   ::  HsSyntacticTokenType 
242+   ->  (forall  r .  (forall  a .  HasSrcSpan  a  =>  a  ->  r ) ->  r )
243+   ->  Maybe Range , HsSyntacticTokenType )
244+ mkFromLocatable tt w =  w \ tok ->  let  mrange =  srcSpanToRange $  getLoc tok in  fmap  (, tt) mrange
133245
134246--  taken from /haskell-language-server/plugins/hls-code-range-plugin/src/Ide/Plugin/CodeRange/Rules.hs
135247
0 commit comments