Skip to content

Commit b45f599

Browse files
committed
hls-class-plugin: Only create placeholders unimplemented methods
1 parent bb6b4e1 commit b45f599

File tree

5 files changed

+86
-2
lines changed

5 files changed

+86
-2
lines changed

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

Lines changed: 25 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ import Control.Monad.Trans.Class
1717
import Control.Monad.Trans.Maybe
1818
import Data.Aeson
1919
import Data.Char
20+
import Data.Either (rights)
2021
import Data.List
2122
import qualified Data.Map.Strict as Map
2223
import Data.Maybe
@@ -192,7 +193,8 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
192193
mkActions docPath diag = do
193194
ident <- findClassIdentifier docPath range
194195
cls <- findClassFromIdentifier docPath ident
195-
lift . traverse mkAction . minDefToMethodGroups . classMinimalDef $ cls
196+
implemented <- findImplementedMethods docPath range
197+
lift . traverse (mkAction . (\\ implemented)) . minDefToMethodGroups . classMinimalDef $ cls
196198
where
197199
range = diag ^. J.range
198200

@@ -212,6 +214,7 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
212214
= InR
213215
$ CodeAction title (Just CodeActionQuickFix) (Just (List [])) Nothing Nothing Nothing (Just cmd) Nothing
214216

217+
findClassIdentifier :: NormalizedFilePath -> Range -> MaybeT IO (Either ModuleName Name)
215218
findClassIdentifier docPath range = do
216219
(hieAstResult, pmap) <- MaybeT . runAction "classplugin" state $ useWithStale GetHieAst docPath
217220
case hieAstResult of
@@ -234,18 +237,38 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
234237
_ -> panic "Ide.Plugin.Class.findClassFromIdentifier"
235238
findClassFromIdentifier _ (Left _) = panic "Ide.Plugin.Class.findClassIdentifier"
236239

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

240259
containRange :: Range -> SrcSpan -> Bool
241260
containRange range x = isInsideSrcSpan (range ^. J.start) x || isInsideSrcSpan (range ^. J.end) x
242261

243262
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
245264

246265
isClassMethodWarning :: T.Text -> Bool
247266
isClassMethodWarning = T.isPrefixOf "• No explicit implementation for"
248267

268+
isInstanceValBind :: ContextInfo -> Bool
269+
isInstanceValBind (ValBind InstanceBind _ _) = True
270+
isInstanceValBind _ = False
271+
249272
minDefToMethodGroups :: BooleanFormula Name -> [[T.Text]]
250273
minDefToMethodGroups = go
251274
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: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
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+
{-# MINIMAL f, g | g, h #-}
15+
16+
instance Test X where
17+
f X = X
18+
f Y = Y
19+
g = _
Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
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+
{-# MINIMAL f, g | g, h #-}
15+
16+
instance Test X where
17+
f X = X
18+
f Y = Y
19+
g = _
20+
h = _
Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
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+
{-# MINIMAL f, g | g, h #-}
15+
16+
instance Test X where
17+
f X = X
18+
f Y = Y

0 commit comments

Comments
 (0)