Skip to content

Commit b7da1f5

Browse files
committed
Provide explicit import in inlay hints
1 parent a1fe52f commit b7da1f5

File tree

2 files changed

+54
-11
lines changed

2 files changed

+54
-11
lines changed

hls-plugin-api/src/Ide/Types.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -504,6 +504,12 @@ instance PluginMethod Request Method_WorkspaceSymbol where
504504
-- Unconditionally enabled, but should it really be?
505505
handlesRequest _ _ _ _ = HandlesRequest
506506

507+
instance PluginMethod Request Method_TextDocumentInlayHint where
508+
handlesRequest _ _ _ _ = HandlesRequest
509+
510+
instance PluginMethod Request Method_InlayHintResolve where
511+
handlesRequest _ _ _ _ = HandlesRequest
512+
507513
instance PluginMethod Request Method_TextDocumentCodeLens where
508514
handlesRequest = pluginEnabledWithFeature plcCodeLensOn
509515

@@ -803,6 +809,12 @@ instance PluginRequestMethod Method_TextDocumentSemanticTokensFull where
803809
instance PluginRequestMethod Method_TextDocumentSemanticTokensFullDelta where
804810
combineResponses _ _ _ _ (x :| _) = x
805811

812+
instance PluginRequestMethod Method_TextDocumentInlayHint where
813+
combineResponses _ _ _ _ (x :| _) = x
814+
815+
instance PluginRequestMethod Method_InlayHintResolve where
816+
combineResponses _ _ _ _ (x :| _) = x
817+
806818
takeLefts :: [a |? b] -> [a]
807819
takeLefts = mapMaybe (\x -> [res | (InL res) <- Just x])
808820

plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs

Lines changed: 42 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
{-# LANGUAGE RecordWildCards #-}
77
{-# LANGUAGE TypeFamilies #-}
88
{-# LANGUAGE ViewPatterns #-}
9+
910
module Ide.Plugin.ExplicitImports
1011
( descriptor
1112
, descriptorForModules
@@ -22,6 +23,7 @@ import Control.Monad.Trans.Except (ExceptT)
2223
import Control.Monad.Trans.Maybe
2324
import qualified Data.Aeson as A (ToJSON (toJSON))
2425
import Data.Aeson.Types (FromJSON)
26+
import Data.Char (isSpace)
2527
import qualified Data.IntMap as IM (IntMap, elems,
2628
fromList, (!?))
2729
import Data.IORef (readIORef)
@@ -44,8 +46,9 @@ import GHC.Generics (Generic)
4446
import Ide.Plugin.Error (PluginError (..),
4547
getNormalizedFilePathE,
4648
handleMaybe)
47-
import Ide.Plugin.RangeMap (filterByRange)
48-
import qualified Ide.Plugin.RangeMap as RM (RangeMap, fromList)
49+
import qualified Ide.Plugin.RangeMap as RM (RangeMap,
50+
filterByRange,
51+
fromList)
4952
import Ide.Plugin.Resolve
5053
import Ide.PluginUtils
5154
import Ide.Types
@@ -98,9 +101,11 @@ descriptorForModules recorder modFilter plId =
98101
-- This plugin provides code lenses
99102
mkPluginHandler SMethod_TextDocumentCodeLens (lensProvider recorder)
100103
<> mkResolveHandler SMethod_CodeLensResolve (lensResolveProvider recorder)
101-
-- This plugin provides code actions
104+
-- This plugin provides inlay hints
105+
<> mkPluginHandler SMethod_TextDocumentInlayHint (inlayHintProvider recorder)
106+
-- <> mkResolveHandler SMethod_InlayHintResolve (inlayHintResolveProvider recorder)
107+
-- This plugin provides code actions
102108
<> codeActionHandlers
103-
104109
}
105110

106111
-- | The actual command handler
@@ -146,12 +151,13 @@ lensProvider _ state _ CodeLensParams {_textDocument = TextDocumentIdentifier {
146151
, _range = range
147152
, _command = Nothing }
148153

154+
149155
lensResolveProvider :: Recorder (WithPriority Log) -> ResolveFunction IdeState IAResolveData 'Method_CodeLensResolve
150156
lensResolveProvider _ ideState plId cl uri rd@(ResolveOne _ uid) = do
151157
nfp <- getNormalizedFilePathE uri
152158
(ImportActionsResult{forResolve}, _) <- runActionE "ImportActions" ideState $ useWithStaleE ImportActions nfp
153159
target <- handleMaybe PluginStaleResolve $ forResolve IM.!? uid
154-
let updatedCodeLens = cl & L.command ?~ mkCommand plId target
160+
let updatedCodeLens = cl & L.command ?~ mkCommand plId target
155161
pure updatedCodeLens
156162
where mkCommand :: PluginId -> ImportEdit -> Command
157163
mkCommand pId (ImportEdit{ieResType, ieText}) =
@@ -166,6 +172,35 @@ lensResolveProvider _ ideState plId cl uri rd@(ResolveOne _ uid) = do
166172
lensResolveProvider _ _ _ _ _ rd = do
167173
throwError $ PluginInvalidParams (T.pack $ "Unexpected argument for lens resolve handler: " <> show rd)
168174

175+
176+
inlayHintProvider :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState 'Method_TextDocumentInlayHint
177+
inlayHintProvider _ state _ InlayHintParams {_textDocument = TextDocumentIdentifier {_uri}} = do
178+
nfp <- getNormalizedFilePathE _uri
179+
(ImportActionsResult {forLens, forResolve}, pm) <- runActionE "ImportActions" state $ useWithStaleE ImportActions nfp
180+
let inlayHints = [ generateInlayHints newRange ie
181+
| (range, int) <- forLens
182+
, Just newRange <- [toCurrentRange pm range]
183+
, Just ie <- [forResolve IM.!? int]]
184+
pure $ InL inlayHints
185+
where
186+
generateInlayHints :: Range -> ImportEdit -> InlayHint
187+
generateInlayHints Range {_end} ie =
188+
InlayHint { _position = _end
189+
, _label = mkLabel ie
190+
, _kind = Nothing
191+
, _textEdits = Nothing
192+
, _tooltip = Nothing
193+
, _paddingLeft = Just True
194+
, _paddingRight = Nothing
195+
, _data_ = Nothing
196+
}
197+
mkLabel :: ImportEdit -> T.Text |? [InlayHintLabelPart]
198+
mkLabel (ImportEdit{ieResType, ieText}) =
199+
let title ExplicitImport = abbreviateImportTitle $ (T.intercalate " " . filter (not . T.null) . T.split isSpace . T.dropWhile (/= '(')) ieText
200+
title RefineImport = T.intercalate ", " (T.lines ieText)
201+
in InL $ title ieResType
202+
203+
169204
-- |For explicit imports: If there are any implicit imports, provide both one
170205
-- code action per import to make that specific import explicit, and one code
171206
-- action to turn them all into explicit imports. For refine imports: If there
@@ -176,7 +211,7 @@ codeActionProvider _ ideState _pId (CodeActionParams _ _ TextDocumentIdentifier
176211
nfp <- getNormalizedFilePathE _uri
177212
(ImportActionsResult{forCodeActions}, pm) <- runActionE "ImportActions" ideState $ useWithStaleE ImportActions nfp
178213
newRange <- toCurrentRangeE pm range
179-
let relevantCodeActions = filterByRange newRange forCodeActions
214+
let relevantCodeActions = RM.filterByRange newRange forCodeActions
180215
allExplicit =
181216
[InR $ mkCodeAction "Make all imports explicit" (Just $ A.toJSON $ ExplicitAll _uri)
182217
-- We should only provide this code action if there are any code
@@ -410,7 +445,6 @@ isExplicitImport _ = False
410445
maxColumns :: Int
411446
maxColumns = 120
412447

413-
414448
-- | The title of the command is ideally the minimal explicit import decl, but
415449
-- we don't want to create a really massive code lens (and the decl can be extremely large!).
416450
-- So we abbreviate it to fit a max column size, and indicate how many more items are in the list
@@ -462,10 +496,7 @@ filterByImport (ImportDecl{ideclHiding = Just (_, L _ names)})
462496
else Nothing
463497
where importedNames = S.fromList $ map (ieName . unLoc) names
464498
res = flip Map.filter avails $ \a ->
465-
any (`S.member` importedNames)
466-
$ concatMap
467-
getAvailNames
468-
a
499+
any (any (`S.member` importedNames) . getAvailNames) a
469500
allFilteredAvailsNames = S.fromList
470501
$ concatMap getAvailNames
471502
$ mconcat

0 commit comments

Comments
 (0)