@@ -17,6 +17,7 @@ import Control.Monad.Trans.Class
17
17
import Control.Monad.Trans.Maybe
18
18
import Data.Aeson
19
19
import Data.Char
20
+ import Data.Either (rights )
20
21
import Data.List
21
22
import qualified Data.Map.Strict as Map
22
23
import Data.Maybe
@@ -192,7 +193,8 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
192
193
mkActions docPath diag = do
193
194
ident <- findClassIdentifier docPath range
194
195
cls <- findClassFromIdentifier docPath ident
195
- lift . traverse mkAction . minDefToMethodGroups . classMinimalDef $ cls
196
+ implemented <- findImplementedMethods docPath range
197
+ lift . traverse (mkAction . (\\ implemented)) . minDefToMethodGroups . classMinimalDef $ cls
196
198
where
197
199
range = diag ^. J. range
198
200
@@ -212,6 +214,7 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
212
214
= InR
213
215
$ CodeAction title (Just CodeActionQuickFix ) (Just (List [] )) Nothing Nothing Nothing (Just cmd) Nothing
214
216
217
+ findClassIdentifier :: NormalizedFilePath -> Range -> MaybeT IO (Either ModuleName Name )
215
218
findClassIdentifier docPath range = do
216
219
(hieAstResult, pmap) <- MaybeT . runAction " classplugin" state $ useWithStale GetHieAst docPath
217
220
case hieAstResult of
@@ -234,18 +237,38 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
234
237
_ -> panic " Ide.Plugin.Class.findClassFromIdentifier"
235
238
findClassFromIdentifier _ (Left _) = panic " Ide.Plugin.Class.findClassIdentifier"
236
239
240
+ findImplementedMethods :: NormalizedFilePath -> Range -> MaybeT IO [T. Text ]
241
+ findImplementedMethods docPath range = do
242
+ (HAR {hieAst = hf}, pmap) <- MaybeT . runAction " classplugin" state $ useWithStale GetHieAst docPath
243
+ pure
244
+ $ concat
245
+ $ pointCommand hf (fromJust (fromCurrentRange pmap range) ^. J. start & J. character -~ 1 )
246
+ $ map (T. pack . getOccString) . rights . findInstanceValBindIdentifiers
247
+
248
+ findInstanceValBindIdentifiers :: HieAST a -> [Identifier ]
249
+ findInstanceValBindIdentifiers ast
250
+ | Map. null (getNodeIds ast) = concatMap findInstanceValBindIdentifiers (nodeChildren ast)
251
+ | otherwise = Map. keys
252
+ . Map. filter (not . Set. null )
253
+ . Map. map (Set. filter isInstanceValBind . identInfo)
254
+ $ getNodeIds ast
255
+
237
256
ghostSpan :: RealSrcSpan
238
257
ghostSpan = realSrcLocSpan $ mkRealSrcLoc (fsLit " <haskell-language-sever>" ) 1 1
239
258
240
259
containRange :: Range -> SrcSpan -> Bool
241
260
containRange range x = isInsideSrcSpan (range ^. J. start) x || isInsideSrcSpan (range ^. J. end) x
242
261
243
262
isClassNodeIdentifier :: IdentifierDetails a -> Bool
244
- isClassNodeIdentifier ident = (isNothing . identType) ident && Use `Set.member` ( identInfo ident)
263
+ isClassNodeIdentifier ident = (isNothing . identType) ident && Use `Set.member` identInfo ident
245
264
246
265
isClassMethodWarning :: T. Text -> Bool
247
266
isClassMethodWarning = T. isPrefixOf " • No explicit implementation for"
248
267
268
+ isInstanceValBind :: ContextInfo -> Bool
269
+ isInstanceValBind (ValBind InstanceBind _ _) = True
270
+ isInstanceValBind _ = False
271
+
249
272
minDefToMethodGroups :: BooleanFormula Name -> [[T. Text ]]
250
273
minDefToMethodGroups = go
251
274
where
0 commit comments