@@ -17,6 +17,7 @@ module Ide.Plugin.ExplicitImports
17
17
18
18
import Control.DeepSeq
19
19
import Control.Lens (_Just , (&) , (?~) , (^?) )
20
+ import Control.Monad (guard )
20
21
import Control.Monad.Error.Class (MonadError (throwError ))
21
22
import Control.Monad.IO.Class
22
23
import Control.Monad.Trans.Class (lift )
@@ -25,14 +26,15 @@ import Control.Monad.Trans.Maybe
25
26
import qualified Data.Aeson as A (ToJSON (toJSON ))
26
27
import Data.Aeson.Types (FromJSON )
27
28
import Data.Char (isSpace )
29
+ import Data.Either (lefts )
28
30
import Data.Functor ((<&>) )
29
31
import qualified Data.IntMap as IM (IntMap , elems ,
30
32
fromList , (!?) )
31
33
import Data.IORef (readIORef )
32
34
import Data.List (singleton )
33
35
import qualified Data.Map.Strict as Map
34
36
import Data.Maybe (isJust , isNothing ,
35
- mapMaybe )
37
+ listToMaybe , mapMaybe )
36
38
import qualified Data.Set as S
37
39
import Data.String (fromString )
38
40
import qualified Data.Text as T
@@ -46,6 +48,7 @@ import Development.IDE.Core.PluginUtils
46
48
import Development.IDE.Core.PositionMapping
47
49
import qualified Development.IDE.Core.Shake as Shake
48
50
import Development.IDE.GHC.Compat hiding ((<+>) )
51
+ import Development.IDE.GHC.Compat.Util (mkFastString )
49
52
import Development.IDE.Graph.Classes
50
53
import GHC.Generics (Generic )
51
54
import Ide.Plugin.Error (PluginError (.. ),
@@ -109,6 +112,7 @@ descriptorForModules recorder modFilter plId =
109
112
<> mkResolveHandler SMethod_CodeLensResolve (lensResolveProvider recorder)
110
113
-- This plugin provides inlay hints
111
114
<> mkPluginHandler SMethod_TextDocumentInlayHint (inlayHintProvider recorder)
115
+ <> mkPluginHandler SMethod_TextDocumentInlayHint (importPackageInlayHintProvider recorder)
112
116
-- This plugin provides code actions
113
117
<> codeActionHandlers
114
118
}
@@ -234,6 +238,73 @@ inlayHintProvider _ state _ InlayHintParams {_textDocument = TextDocumentIdentif
234
238
title RefineImport = Nothing -- does not provide imports statements that can be refined via inlay hints
235
239
in title ieResType
236
240
241
+ -- | Provide inlay hints that show which package a module is imported from.
242
+ importPackageInlayHintProvider :: Recorder (WithPriority Log ) -> PluginMethodHandler IdeState 'Method_TextDocumentInlayHint
243
+ importPackageInlayHintProvider _ state _ InlayHintParams {_textDocument = TextDocumentIdentifier {_uri}, _range = visibleRange} =
244
+ if isInlayHintsSupported state
245
+ then do
246
+ nfp <- getNormalizedFilePathE _uri
247
+ (hscEnvEq, _) <- runActionE " ImportPackageInlayHint.GhcSessionDeps" state $ useWithStaleE GhcSessionDeps nfp
248
+ (HAR {hieAst, hieModule}, pmap) <- runActionE " ImportPackageInlayHint.GetHieAst" state $ useWithStaleE GetHieAst nfp
249
+ ast <- handleMaybe
250
+ (PluginRuleFailed " GetHieAst" )
251
+ (getAsts hieAst Map. !? (HiePath . mkFastString . fromNormalizedFilePath) nfp)
252
+ hintsInfo <- liftIO $ getAllImportedPackagesHints (hscEnv hscEnvEq) (moduleName hieModule) ast
253
+ -- Filter out empty package names
254
+ let selectedHintsInfo = hintsInfo & filter (\ (_, mbPkg) -> (not . T. null ) mbPkg)
255
+ let inlayHints = [ generateInlayHint newRange txt
256
+ | (range, txt) <- selectedHintsInfo
257
+ , Just newRange <- [toCurrentRange pmap range]
258
+ , isSubrangeOf newRange visibleRange]
259
+ pure $ InL inlayHints
260
+ -- When the client does not support inlay hints, do not display anything
261
+ else pure $ InL []
262
+ where
263
+ generateInlayHint :: Range -> T. Text -> InlayHint
264
+ generateInlayHint (Range start _) txt =
265
+ InlayHint { _position = start
266
+ , _label = InL txt
267
+ , _kind = Nothing
268
+ , _textEdits = Nothing
269
+ , _tooltip = Nothing
270
+ , _paddingLeft = Nothing
271
+ , _paddingRight = Just True
272
+ , _data_ = Nothing
273
+ }
274
+
275
+ -- | Get inlay hints information for all imported packages
276
+ getAllImportedPackagesHints :: HscEnv -> ModuleName -> HieAST a -> IO [(Range , T. Text )]
277
+ getAllImportedPackagesHints env currentModuleName = go
278
+ where
279
+ go :: HieAST a -> IO [(Range , T. Text )]
280
+ go ast = do
281
+ let range = realSrcSpanToRange $ nodeSpan ast
282
+ childrenResults <- traverse go (nodeChildren ast)
283
+ mbPackage <- getImportedPackage ast
284
+ return $ case mbPackage of
285
+ Nothing -> mconcat childrenResults
286
+ Just package -> (range, package) : mconcat childrenResults
287
+
288
+ getImportedPackage :: HieAST a -> IO (Maybe T. Text )
289
+ getImportedPackage ast = runMaybeT $ do
290
+ nodeInfo <- MaybeT $ return $ sourceNodeInfo ast
291
+ moduleName <- MaybeT $ return $
292
+ nodeIdentifiers nodeInfo
293
+ & Map. keys
294
+ & lefts
295
+ & listToMaybe
296
+ filteredModuleName <- MaybeT $ return $
297
+ guard (moduleName /= currentModuleName) >> Just moduleName
298
+ txt <- MaybeT $ packageNameForModuleName filteredModuleName
299
+ return $ " \" " <> txt <> " \" "
300
+
301
+ packageNameForModuleName :: ModuleName -> IO (Maybe T. Text )
302
+ packageNameForModuleName modName = runMaybeT $ do
303
+ mod <- MaybeT $ findImportedModule env modName
304
+ let pid = moduleUnit mod
305
+ conf <- MaybeT $ return $ lookupUnit env pid
306
+ return $ T. pack $ unitPackageNameString conf
307
+
237
308
238
309
-- | For explicit imports: If there are any implicit imports, provide both one
239
310
-- code action per import to make that specific import explicit, and one code
0 commit comments