1
1
{-# LANGUAGE CPP #-}
2
2
{-# LANGUAGE DeriveAnyClass #-}
3
3
{-# LANGUAGE DeriveGeneric #-}
4
+ {-# LANGUAGE LambdaCase #-}
4
5
{-# LANGUAGE OverloadedStrings #-}
5
6
{-# LANGUAGE RecordWildCards #-}
6
7
{-# LANGUAGE TypeFamilies #-}
@@ -17,11 +18,12 @@ import Control.Monad.Trans.Class
17
18
import Control.Monad.Trans.Maybe
18
19
import Data.Aeson
19
20
import Data.Char
21
+ import Data.Either (rights )
20
22
import Data.List
21
23
import qualified Data.Map.Strict as Map
22
24
import Data.Maybe
23
- import qualified Data.Text as T
24
25
import qualified Data.Set as Set
26
+ import qualified Data.Text as T
25
27
import Development.IDE hiding (pluginHandlers )
26
28
import Development.IDE.Core.PositionMapping (fromCurrentRange ,
27
29
toCurrentRange )
@@ -40,7 +42,7 @@ import Language.LSP.Types
40
42
import qualified Language.LSP.Types.Lens as J
41
43
42
44
#if MIN_VERSION_ghc(9,2,0)
43
- import GHC.Hs (AnnsModule (AnnsModule ))
45
+ import GHC.Hs (AnnsModule (AnnsModule ))
44
46
import GHC.Parser.Annotation
45
47
#endif
46
48
@@ -190,9 +192,16 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
190
192
methodDiags = filter (\ d -> isClassMethodWarning (d ^. J. message)) ghcDiags
191
193
192
194
mkActions docPath diag = do
193
- ident <- findClassIdentifier docPath range
195
+ (HAR {hieAst = ast}, pmap) <-
196
+ MaybeT . runAction " classplugin" state $ useWithStale GetHieAst docPath
197
+ instancePosition <- MaybeT . pure $
198
+ fromCurrentRange pmap range ^? _Just . J. start
199
+ & fmap (J. character -~ 1 )
200
+
201
+ ident <- findClassIdentifier ast instancePosition
194
202
cls <- findClassFromIdentifier docPath ident
195
- lift . traverse mkAction . minDefToMethodGroups . classMinimalDef $ cls
203
+ implemented <- findImplementedMethods ast instancePosition
204
+ lift . traverse (mkAction . (\\ implemented)) . minDefToMethodGroups . classMinimalDef $ cls
196
205
where
197
206
range = diag ^. J. range
198
207
@@ -212,16 +221,14 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
212
221
= InR
213
222
$ CodeAction title (Just CodeActionQuickFix ) (Just (List [] )) Nothing Nothing Nothing (Just cmd) Nothing
214
223
215
- findClassIdentifier docPath range = do
216
- (hieAstResult, pmap) <- MaybeT . runAction " classplugin" state $ useWithStale GetHieAst docPath
217
- case hieAstResult of
218
- HAR {hieAst = hf} ->
219
- pure
220
- $ head . head
221
- $ pointCommand hf (fromJust (fromCurrentRange pmap range) ^. J. start & J. character -~ 1 )
222
- ( (Map. keys . Map. filter isClassNodeIdentifier . Compat. getNodeIds)
223
- <=< nodeChildren
224
- )
224
+ findClassIdentifier :: HieASTs a -> Position -> MaybeT IO (Either ModuleName Name )
225
+ findClassIdentifier ast instancePosition =
226
+ pure
227
+ $ head . head
228
+ $ pointCommand ast instancePosition
229
+ ( (Map. keys . Map. filter isClassNodeIdentifier . Compat. getNodeIds)
230
+ <=< nodeChildren
231
+ )
225
232
226
233
findClassFromIdentifier docPath (Right name) = do
227
234
(hscEnv -> hscenv, _) <- MaybeT . runAction " classplugin" state $ useWithStale GhcSessionDeps docPath
@@ -234,18 +241,38 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
234
241
_ -> panic " Ide.Plugin.Class.findClassFromIdentifier"
235
242
findClassFromIdentifier _ (Left _) = panic " Ide.Plugin.Class.findClassIdentifier"
236
243
244
+ findImplementedMethods :: HieASTs a -> Position -> MaybeT IO [T. Text ]
245
+ findImplementedMethods asts instancePosition = do
246
+ pure
247
+ $ concat
248
+ $ pointCommand asts instancePosition
249
+ $ map (T. pack . getOccString) . rights . findInstanceValBindIdentifiers
250
+
251
+ -- | Recurses through the given AST to find identifiers which are
252
+ -- 'InstanceValBind's.
253
+ findInstanceValBindIdentifiers :: HieAST a -> [Identifier ]
254
+ findInstanceValBindIdentifiers ast =
255
+ let valBindIds = Map. keys
256
+ . Map. filter (any isInstanceValBind . identInfo)
257
+ $ getNodeIds ast
258
+ in valBindIds <> concatMap findInstanceValBindIdentifiers (nodeChildren ast)
259
+
237
260
ghostSpan :: RealSrcSpan
238
261
ghostSpan = realSrcLocSpan $ mkRealSrcLoc (fsLit " <haskell-language-sever>" ) 1 1
239
262
240
263
containRange :: Range -> SrcSpan -> Bool
241
264
containRange range x = isInsideSrcSpan (range ^. J. start) x || isInsideSrcSpan (range ^. J. end) x
242
265
243
266
isClassNodeIdentifier :: IdentifierDetails a -> Bool
244
- isClassNodeIdentifier ident = (isNothing . identType) ident && Use `Set.member` ( identInfo ident)
267
+ isClassNodeIdentifier ident = (isNothing . identType) ident && Use `Set.member` identInfo ident
245
268
246
269
isClassMethodWarning :: T. Text -> Bool
247
270
isClassMethodWarning = T. isPrefixOf " • No explicit implementation for"
248
271
272
+ isInstanceValBind :: ContextInfo -> Bool
273
+ isInstanceValBind (ValBind InstanceBind _ _) = True
274
+ isInstanceValBind _ = False
275
+
249
276
minDefToMethodGroups :: BooleanFormula Name -> [[T. Text ]]
250
277
minDefToMethodGroups = go
251
278
where
0 commit comments