Skip to content

Commit d868d80

Browse files
committed
hls-class-plugin: Only create placeholders for unimplemented methods
1 parent 09968a1 commit d868d80

File tree

5 files changed

+112
-15
lines changed

5 files changed

+112
-15
lines changed

plugins/hls-class-plugin/src/Ide/Plugin/Class.hs

Lines changed: 42 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE DeriveAnyClass #-}
33
{-# LANGUAGE DeriveGeneric #-}
4+
{-# LANGUAGE LambdaCase #-}
45
{-# LANGUAGE OverloadedStrings #-}
56
{-# LANGUAGE RecordWildCards #-}
67
{-# LANGUAGE TypeFamilies #-}
@@ -17,11 +18,12 @@ import Control.Monad.Trans.Class
1718
import Control.Monad.Trans.Maybe
1819
import Data.Aeson
1920
import Data.Char
21+
import Data.Either (rights)
2022
import Data.List
2123
import qualified Data.Map.Strict as Map
2224
import Data.Maybe
23-
import qualified Data.Text as T
2425
import qualified Data.Set as Set
26+
import qualified Data.Text as T
2527
import Development.IDE hiding (pluginHandlers)
2628
import Development.IDE.Core.PositionMapping (fromCurrentRange,
2729
toCurrentRange)
@@ -40,7 +42,7 @@ import Language.LSP.Types
4042
import qualified Language.LSP.Types.Lens as J
4143

4244
#if MIN_VERSION_ghc(9,2,0)
43-
import GHC.Hs (AnnsModule(AnnsModule))
45+
import GHC.Hs (AnnsModule (AnnsModule))
4446
import GHC.Parser.Annotation
4547
#endif
4648

@@ -190,9 +192,16 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
190192
methodDiags = filter (\d -> isClassMethodWarning (d ^. J.message)) ghcDiags
191193

192194
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
194202
cls <- findClassFromIdentifier docPath ident
195-
lift . traverse mkAction . minDefToMethodGroups . classMinimalDef $ cls
203+
implemented <- findImplementedMethods ast instancePosition
204+
lift . traverse (mkAction . (\\ implemented)) . minDefToMethodGroups . classMinimalDef $ cls
196205
where
197206
range = diag ^. J.range
198207

@@ -212,16 +221,14 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
212221
= InR
213222
$ CodeAction title (Just CodeActionQuickFix) (Just (List [])) Nothing Nothing Nothing (Just cmd) Nothing
214223

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+
)
225232

226233
findClassFromIdentifier docPath (Right name) = do
227234
(hscEnv -> hscenv, _) <- MaybeT . runAction "classplugin" state $ useWithStale GhcSessionDeps docPath
@@ -234,18 +241,38 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
234241
_ -> panic "Ide.Plugin.Class.findClassFromIdentifier"
235242
findClassFromIdentifier _ (Left _) = panic "Ide.Plugin.Class.findClassIdentifier"
236243

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+
237260
ghostSpan :: RealSrcSpan
238261
ghostSpan = realSrcLocSpan $ mkRealSrcLoc (fsLit "<haskell-language-sever>") 1 1
239262

240263
containRange :: Range -> SrcSpan -> Bool
241264
containRange range x = isInsideSrcSpan (range ^. J.start) x || isInsideSrcSpan (range ^. J.end) x
242265

243266
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
245268

246269
isClassMethodWarning :: T.Text -> Bool
247270
isClassMethodWarning = T.isPrefixOf "• No explicit implementation for"
248271

272+
isInstanceValBind :: ContextInfo -> Bool
273+
isInstanceValBind (ValBind InstanceBind _ _) = True
274+
isInstanceValBind _ = False
275+
249276
minDefToMethodGroups :: BooleanFormula Name -> [[T.Text]]
250277
minDefToMethodGroups = go
251278
where

plugins/hls-class-plugin/test/Main.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,10 @@ tests = testGroup
4848
executeCodeAction _fAction
4949
, goldenWithClass "Creates a placeholder for '==' with extra lines" "T5" "" $ \(eqAction:_) -> do
5050
executeCodeAction eqAction
51+
, goldenWithClass "Creates a placeholder for only the unimplemented methods of multiple methods" "T6" "1" $ \(gAction:_) -> do
52+
executeCodeAction gAction
53+
, goldenWithClass "Creates a placeholder for other two multiple methods" "T6" "2" $ \(_:ghAction:_) -> do
54+
executeCodeAction ghAction
5155
]
5256

5357
_CACodeAction :: Prism' (Command |? CodeAction) CodeAction
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
module T6 where
2+
3+
data X = X | Y
4+
5+
class Test a where
6+
f :: a -> a
7+
f = h
8+
9+
g :: a
10+
11+
h :: a -> a
12+
h = f
13+
14+
i :: a
15+
16+
{-# MINIMAL f, g, i | g, h #-}
17+
18+
instance Test X where
19+
f X = X
20+
f Y = Y
21+
i = undefined
22+
g = _
Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
module T6 where
2+
3+
data X = X | Y
4+
5+
class Test a where
6+
f :: a -> a
7+
f = h
8+
9+
g :: a
10+
11+
h :: a -> a
12+
h = f
13+
14+
i :: a
15+
16+
{-# MINIMAL f, g, i | g, h #-}
17+
18+
instance Test X where
19+
f X = X
20+
f Y = Y
21+
i = undefined
22+
g = _
23+
h = _
Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,21 @@
1+
module T6 where
2+
3+
data X = X | Y
4+
5+
class Test a where
6+
f :: a -> a
7+
f = h
8+
9+
g :: a
10+
11+
h :: a -> a
12+
h = f
13+
14+
i :: a
15+
16+
{-# MINIMAL f, g, i | g, h #-}
17+
18+
instance Test X where
19+
f X = X
20+
f Y = Y
21+
i = undefined

0 commit comments

Comments
 (0)