6
6
{-# LANGUAGE RecordWildCards #-}
7
7
{-# LANGUAGE TypeFamilies #-}
8
8
{-# LANGUAGE ViewPatterns #-}
9
+
9
10
module Ide.Plugin.ExplicitImports
10
11
( descriptor
11
12
, descriptorForModules
@@ -22,6 +23,7 @@ import Control.Monad.Trans.Except (ExceptT)
22
23
import Control.Monad.Trans.Maybe
23
24
import qualified Data.Aeson as A (ToJSON (toJSON ))
24
25
import Data.Aeson.Types (FromJSON )
26
+ import Data.Char (isSpace )
25
27
import qualified Data.IntMap as IM (IntMap , elems ,
26
28
fromList , (!?) )
27
29
import Data.IORef (readIORef )
@@ -44,8 +46,9 @@ import GHC.Generics (Generic)
44
46
import Ide.Plugin.Error (PluginError (.. ),
45
47
getNormalizedFilePathE ,
46
48
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 )
49
52
import Ide.Plugin.Resolve
50
53
import Ide.PluginUtils
51
54
import Ide.Types
@@ -98,9 +101,11 @@ descriptorForModules recorder modFilter plId =
98
101
-- This plugin provides code lenses
99
102
mkPluginHandler SMethod_TextDocumentCodeLens (lensProvider recorder)
100
103
<> 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
102
108
<> codeActionHandlers
103
-
104
109
}
105
110
106
111
-- | The actual command handler
@@ -146,12 +151,13 @@ lensProvider _ state _ CodeLensParams {_textDocument = TextDocumentIdentifier {
146
151
, _range = range
147
152
, _command = Nothing }
148
153
154
+
149
155
lensResolveProvider :: Recorder (WithPriority Log ) -> ResolveFunction IdeState IAResolveData 'Method_CodeLensResolve
150
156
lensResolveProvider _ ideState plId cl uri rd@ (ResolveOne _ uid) = do
151
157
nfp <- getNormalizedFilePathE uri
152
158
(ImportActionsResult {forResolve}, _) <- runActionE " ImportActions" ideState $ useWithStaleE ImportActions nfp
153
159
target <- handleMaybe PluginStaleResolve $ forResolve IM. !? uid
154
- let updatedCodeLens = cl & L. command ?~ mkCommand plId target
160
+ let updatedCodeLens = cl & L. command ?~ mkCommand plId target
155
161
pure updatedCodeLens
156
162
where mkCommand :: PluginId -> ImportEdit -> Command
157
163
mkCommand pId (ImportEdit {ieResType, ieText}) =
@@ -166,6 +172,35 @@ lensResolveProvider _ ideState plId cl uri rd@(ResolveOne _ uid) = do
166
172
lensResolveProvider _ _ _ _ _ rd = do
167
173
throwError $ PluginInvalidParams (T. pack $ " Unexpected argument for lens resolve handler: " <> show rd)
168
174
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
+
169
204
-- | For explicit imports: If there are any implicit imports, provide both one
170
205
-- code action per import to make that specific import explicit, and one code
171
206
-- action to turn them all into explicit imports. For refine imports: If there
@@ -176,7 +211,7 @@ codeActionProvider _ ideState _pId (CodeActionParams _ _ TextDocumentIdentifier
176
211
nfp <- getNormalizedFilePathE _uri
177
212
(ImportActionsResult {forCodeActions}, pm) <- runActionE " ImportActions" ideState $ useWithStaleE ImportActions nfp
178
213
newRange <- toCurrentRangeE pm range
179
- let relevantCodeActions = filterByRange newRange forCodeActions
214
+ let relevantCodeActions = RM. filterByRange newRange forCodeActions
180
215
allExplicit =
181
216
[InR $ mkCodeAction " Make all imports explicit" (Just $ A. toJSON $ ExplicitAll _uri)
182
217
-- We should only provide this code action if there are any code
@@ -410,7 +445,6 @@ isExplicitImport _ = False
410
445
maxColumns :: Int
411
446
maxColumns = 120
412
447
413
-
414
448
-- | The title of the command is ideally the minimal explicit import decl, but
415
449
-- we don't want to create a really massive code lens (and the decl can be extremely large!).
416
450
-- 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)})
462
496
else Nothing
463
497
where importedNames = S. fromList $ map (ieName . unLoc) names
464
498
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
469
500
allFilteredAvailsNames = S. fromList
470
501
$ concatMap getAvailNames
471
502
$ mconcat
0 commit comments