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