Skip to content

Commit 3461823

Browse files
hls-class-plugin enhancement (#2920)
* hls-class-plugin enhancement * Comment to be compatible * Add HasSrcSpan instances * hls-class-plugin enhancement * Comment to be compatible * Add HasSrcSpan instances * Compitable fix * Qualified name * Fix compatibility * Resolve reviews * Rename test files Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 907a6e6 commit 3461823

36 files changed

+961
-297
lines changed

plugins/hls-class-plugin/README.md

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
# Class Plugin
2+
3+
The class plugin provides handy operations about class, includes:
4+
5+
1. Code action to add minimal class definition methods.
6+
2. Type lens about missing type signatures for instance methods.
7+
8+
## Demo
9+
10+
![Code Actions](codeactions.gif)
11+
12+
![Code Lens](codelens.gif)
876 KB
Loading

plugins/hls-class-plugin/codelens.gif

192 KB
Loading

plugins/hls-class-plugin/hls-class-plugin.cabal

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,13 +22,22 @@ extra-source-files:
2222

2323
library
2424
exposed-modules: Ide.Plugin.Class
25+
other-modules: Ide.Plugin.Class.CodeAction
26+
, Ide.Plugin.Class.CodeLens
27+
, Ide.Plugin.Class.ExactPrint
28+
, Ide.Plugin.Class.Types
29+
, Ide.Plugin.Class.Utils
2530
hs-source-dirs: src
2631
build-depends:
2732
, aeson
2833
, base >=4.12 && <5
2934
, containers
35+
, deepseq
36+
, extra
3037
, ghc
3138
, ghcide ^>=1.7
39+
, ghc-boot-th
40+
, hls-graph
3241
, hls-plugin-api ^>=1.4
3342
, lens
3443
, lsp
@@ -44,8 +53,9 @@ library
4453
default-extensions:
4554
DataKinds
4655
TypeOperators
56+
OverloadedStrings
4757

48-
ghc-options: -Wno-unticked-promoted-constructors
58+
ghc-options: -Wall -Wno-unticked-promoted-constructors -Wno-name-shadowing
4959

5060
test-suite tests
5161
type: exitcode-stdio-1.0
@@ -54,10 +64,12 @@ test-suite tests
5464
main-is: Main.hs
5565
ghc-options: -threaded -rtsopts -with-rtsopts=-N
5666
build-depends:
67+
, aeson
5768
, base
5869
, filepath
5970
, ghcide
6071
, hls-class-plugin
72+
, hls-plugin-api
6173
, hls-test-utils ^>=1.3
6274
, lens
6375
, lsp-types
Lines changed: 19 additions & 288 deletions
Original file line numberDiff line numberDiff line change
@@ -1,295 +1,26 @@
1-
{-# LANGUAGE CPP #-}
2-
{-# LANGUAGE DeriveAnyClass #-}
3-
{-# LANGUAGE DeriveGeneric #-}
4-
{-# LANGUAGE LambdaCase #-}
5-
{-# LANGUAGE OverloadedStrings #-}
6-
{-# LANGUAGE RecordWildCards #-}
7-
{-# LANGUAGE TypeFamilies #-}
8-
{-# LANGUAGE ViewPatterns #-}
9-
module Ide.Plugin.Class
10-
( descriptor,
11-
Log (..)
12-
) where
1+
module Ide.Plugin.Class (descriptor, Log(..)) where
132

14-
import Control.Applicative
15-
import Control.Lens hiding (List, use)
16-
import Control.Monad
17-
import Control.Monad.IO.Class
18-
import Control.Monad.Trans.Class
19-
import Control.Monad.Trans.Maybe
20-
import Data.Aeson
21-
import Data.Char
22-
import Data.Either (rights)
23-
import Data.List
24-
import qualified Data.Map.Strict as Map
25-
import Data.Maybe
26-
import qualified Data.Set as Set
27-
import qualified Data.Text as T
28-
import Development.IDE hiding (pluginHandlers)
29-
import Development.IDE.Core.PositionMapping (fromCurrentRange,
30-
toCurrentRange)
31-
import Development.IDE.GHC.Compat as Compat hiding (locA,
32-
(<+>))
33-
import Development.IDE.GHC.Compat.Util
34-
import Development.IDE.Spans.AtPoint
35-
import qualified GHC.Generics as Generics
36-
import Ide.PluginUtils
3+
import Development.IDE (IdeState, Recorder, WithPriority)
4+
import Ide.Plugin.Class.CodeAction
5+
import Ide.Plugin.Class.CodeLens
6+
import Ide.Plugin.Class.Types
377
import Ide.Types
38-
import Language.Haskell.GHC.ExactPrint
39-
import Language.Haskell.GHC.ExactPrint.Parsers (parseDecl)
40-
import Language.Haskell.GHC.ExactPrint.Types hiding (GhcPs, Parens)
41-
import Language.Haskell.GHC.ExactPrint.Utils (rs)
42-
import Language.LSP.Server
438
import Language.LSP.Types
44-
import qualified Language.LSP.Types.Lens as J
45-
46-
#if MIN_VERSION_ghc(9,2,0)
47-
import GHC.Hs (AnnsModule (AnnsModule))
48-
import GHC.Parser.Annotation
49-
#endif
50-
51-
data Log
52-
= LogImplementedMethods Class [T.Text]
53-
54-
instance Pretty Log where
55-
pretty = \case
56-
LogImplementedMethods cls methods ->
57-
pretty ("Detected implmented methods for class" :: String)
58-
<+> pretty (show (getOccString cls) <> ":") -- 'show' is used here to add quotes around the class name
59-
<+> pretty methods
609

6110
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
6211
descriptor recorder plId = (defaultPluginDescriptor plId)
63-
{ pluginCommands = commands
64-
, pluginHandlers = mkPluginHandler STextDocumentCodeAction (codeAction recorder)
65-
}
66-
67-
commands :: [PluginCommand IdeState]
68-
commands
69-
= [ PluginCommand "addMinimalMethodPlaceholders" "add placeholders for minimal methods" addMethodPlaceholders
12+
{ pluginCommands = commands plId
13+
, pluginRules = rules recorder
14+
, pluginHandlers = mkPluginHandler STextDocumentCodeAction (codeAction recorder)
15+
<> mkPluginHandler STextDocumentCodeLens codeLens
16+
, pluginConfigDescriptor =
17+
defaultConfigDescriptor { configCustomConfig = mkCustomConfig properties }
18+
}
19+
20+
commands :: PluginId -> [PluginCommand IdeState]
21+
commands plId
22+
= [ PluginCommand codeActionCommandId
23+
"add placeholders for minimal methods" (addMethodPlaceholders plId)
24+
, PluginCommand typeLensCommandId
25+
"add type signatures for instance methods" codeLensCommandHandler
7026
]
71-
72-
-- | Parameter for the addMethods PluginCommand.
73-
data AddMinimalMethodsParams = AddMinimalMethodsParams
74-
{ uri :: Uri
75-
, range :: Range
76-
, methodGroup :: List T.Text
77-
}
78-
deriving (Show, Eq, Generics.Generic, ToJSON, FromJSON)
79-
80-
addMethodPlaceholders :: CommandFunction IdeState AddMinimalMethodsParams
81-
addMethodPlaceholders state AddMinimalMethodsParams{..} = do
82-
caps <- getClientCapabilities
83-
medit <- liftIO $ runMaybeT $ do
84-
docPath <- MaybeT . pure . uriToNormalizedFilePath $ toNormalizedUri uri
85-
pm <- MaybeT . runAction "classplugin" state $ use GetParsedModule docPath
86-
(hsc_dflags . hscEnv -> df) <- MaybeT . runAction "classplugin" state $ use GhcSessionDeps docPath
87-
(old, new) <- makeEditText pm df
88-
pure (workspaceEdit caps old new)
89-
90-
forM_ medit $ \edit ->
91-
sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing edit) (\_ -> pure ())
92-
pure (Right Null)
93-
where
94-
indent = 2
95-
96-
workspaceEdit caps old new
97-
= diffText caps (uri, old) new IncludeDeletions
98-
99-
toMethodName n
100-
| Just (h, _) <- T.uncons n
101-
, not (isAlpha h || h == '_')
102-
= "(" <> n <> ")"
103-
| otherwise
104-
= n
105-
106-
#if MIN_VERSION_ghc(9,2,0)
107-
makeEditText pm df = do
108-
List mDecls <- MaybeT . pure $ traverse (makeMethodDecl df) methodGroup
109-
let ps = makeDeltaAst $ pm_parsed_source pm
110-
old = T.pack $ exactPrint ps
111-
(ps', _, _) = runTransform (addMethodDecls ps mDecls)
112-
new = T.pack $ exactPrint ps'
113-
pure (old, new)
114-
115-
makeMethodDecl df mName =
116-
either (const Nothing) Just . parseDecl df (T.unpack mName) . T.unpack
117-
$ toMethodName mName <> " = _"
118-
119-
addMethodDecls ps mDecls = do
120-
allDecls <- hsDecls ps
121-
let (before, ((L l inst): after)) = break (containRange range . getLoc) allDecls
122-
replaceDecls ps (before ++ (L l (addWhere inst)): (map newLine mDecls ++ after))
123-
where
124-
-- Add `where` keyword for `instance X where` if `where` is missing.
125-
--
126-
-- The `where` in ghc-9.2 is now stored in the instance declaration
127-
-- directly. More precisely, giving an `HsDecl GhcPs`, we have:
128-
-- InstD --> ClsInstD --> ClsInstDecl --> XCClsInstDecl --> (EpAnn [AddEpAnn], AnnSortKey),
129-
-- here `AnnEpAnn` keeps the track of Anns.
130-
--
131-
-- See the link for the original definition:
132-
-- https://hackage.haskell.org/package/ghc-9.2.1/docs/Language-Haskell-Syntax-Extension.html#t:XCClsInstDecl
133-
addWhere (InstD xInstD (ClsInstD ext decl@ClsInstDecl{..})) =
134-
let ((EpAnn entry anns comments), key) = cid_ext
135-
in InstD xInstD (ClsInstD ext decl {
136-
cid_ext = (EpAnn
137-
entry
138-
(AddEpAnn AnnWhere (EpaDelta (SameLine 1) []) : anns)
139-
comments
140-
, key)
141-
})
142-
addWhere decl = decl
143-
144-
newLine (L l e) =
145-
let dp = deltaPos 1 indent
146-
in L (noAnnSrcSpanDP (locA l) dp <> l) e
147-
148-
#else
149-
makeEditText pm df = do
150-
List (unzip -> (mAnns, mDecls)) <- MaybeT . pure $ traverse (makeMethodDecl df) methodGroup
151-
let ps = pm_parsed_source pm
152-
anns = relativiseApiAnns ps (pm_annotations pm)
153-
old = T.pack $ exactPrint ps anns
154-
(ps', (anns', _), _) = runTransform (mergeAnns (mergeAnnList mAnns) anns) (addMethodDecls ps mDecls)
155-
new = T.pack $ exactPrint ps' anns'
156-
pure (old, new)
157-
158-
makeMethodDecl df mName =
159-
case parseDecl df (T.unpack mName) . T.unpack $ toMethodName mName <> " = _" of
160-
Right (ann, d) -> Just (setPrecedingLines d 1 indent ann, d)
161-
Left _ -> Nothing
162-
163-
addMethodDecls ps mDecls = do
164-
d <- findInstDecl ps
165-
newSpan <- uniqueSrcSpanT
166-
let
167-
annKey = mkAnnKey d
168-
newAnnKey = AnnKey (rs newSpan) (CN "HsValBinds")
169-
addWhere mkds@(Map.lookup annKey -> Just ann)
170-
= Map.insert newAnnKey ann2 mkds2
171-
where
172-
ann1 = ann
173-
{ annsDP = annsDP ann ++ [(G AnnWhere, DP (0, 1))]
174-
, annCapturedSpan = Just newAnnKey
175-
, annSortKey = Just (fmap (rs . getLoc) mDecls)
176-
}
177-
mkds2 = Map.insert annKey ann1 mkds
178-
ann2 = annNone
179-
{ annEntryDelta = DP (1, indent)
180-
}
181-
addWhere _ = panic "Ide.Plugin.Class.addMethodPlaceholder"
182-
modifyAnnsT addWhere
183-
modifyAnnsT (captureOrderAnnKey newAnnKey mDecls)
184-
foldM (insertAfter d) ps (reverse mDecls)
185-
186-
findInstDecl :: ParsedSource -> Transform (LHsDecl GhcPs)
187-
findInstDecl ps = head . filter (containRange range . getLoc) <$> hsDecls ps
188-
#endif
189-
190-
-- |
191-
-- This implementation is ad-hoc in a sense that the diagnostic detection mechanism is
192-
-- sensitive to the format of diagnostic messages from GHC.
193-
codeAction :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState TextDocumentCodeAction
194-
codeAction recorder state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fromMaybe errorResult) . runMaybeT $ do
195-
docPath <- MaybeT . pure . uriToNormalizedFilePath $ toNormalizedUri uri
196-
actions <- join <$> mapM (mkActions docPath) methodDiags
197-
pure . Right . List $ actions
198-
where
199-
errorResult = Right (List [])
200-
uri = docId ^. J.uri
201-
List diags = context ^. J.diagnostics
202-
203-
ghcDiags = filter (\d -> d ^. J.source == Just "typecheck") diags
204-
methodDiags = filter (\d -> isClassMethodWarning (d ^. J.message)) ghcDiags
205-
206-
mkActions docPath diag = do
207-
(HAR {hieAst = ast}, pmap) <-
208-
MaybeT . runAction "classplugin" state $ useWithStale GetHieAst docPath
209-
instancePosition <- MaybeT . pure $
210-
fromCurrentRange pmap range ^? _Just . J.start
211-
& fmap (J.character -~ 1)
212-
213-
ident <- findClassIdentifier ast instancePosition
214-
cls <- findClassFromIdentifier docPath ident
215-
implemented <- findImplementedMethods ast instancePosition
216-
logWith recorder Info (LogImplementedMethods cls implemented)
217-
lift . traverse (mkAction . (\\ implemented)) . minDefToMethodGroups . classMinimalDef $ cls
218-
where
219-
range = diag ^. J.range
220-
221-
mkAction methodGroup
222-
= pure $ mkCodeAction title $ mkLspCommand plId "addMinimalMethodPlaceholders" title (Just cmdParams)
223-
where
224-
title = mkTitle methodGroup
225-
cmdParams = mkCmdParams methodGroup
226-
227-
mkTitle methodGroup
228-
= "Add placeholders for "
229-
<> mconcat (intersperse ", " (fmap (\m -> "'" <> m <> "'") methodGroup))
230-
231-
mkCmdParams methodGroup = [toJSON (AddMinimalMethodsParams uri range (List methodGroup))]
232-
233-
mkCodeAction title cmd
234-
= InR
235-
$ CodeAction title (Just CodeActionQuickFix) (Just (List [])) Nothing Nothing Nothing (Just cmd) Nothing
236-
237-
findClassIdentifier :: HieASTs a -> Position -> MaybeT IO (Either ModuleName Name)
238-
findClassIdentifier ast instancePosition =
239-
pure
240-
$ head . head
241-
$ pointCommand ast instancePosition
242-
( (Map.keys . Map.filter isClassNodeIdentifier . Compat.getNodeIds)
243-
<=< nodeChildren
244-
)
245-
246-
findClassFromIdentifier docPath (Right name) = do
247-
(hscEnv -> hscenv, _) <- MaybeT . runAction "classplugin" state $ useWithStale GhcSessionDeps docPath
248-
(tmrTypechecked -> thisMod, _) <- MaybeT . runAction "classplugin" state $ useWithStale TypeCheck docPath
249-
MaybeT . fmap snd . initTcWithGbl hscenv thisMod ghostSpan $ do
250-
tcthing <- tcLookup name
251-
case tcthing of
252-
AGlobal (AConLike (RealDataCon con))
253-
| Just cls <- tyConClass_maybe (dataConOrigTyCon con) -> pure cls
254-
_ -> panic "Ide.Plugin.Class.findClassFromIdentifier"
255-
findClassFromIdentifier _ (Left _) = panic "Ide.Plugin.Class.findClassIdentifier"
256-
257-
findImplementedMethods :: HieASTs a -> Position -> MaybeT IO [T.Text]
258-
findImplementedMethods asts instancePosition = do
259-
pure
260-
$ concat
261-
$ pointCommand asts instancePosition
262-
$ map (T.pack . getOccString) . rights . findInstanceValBindIdentifiers
263-
264-
-- | Recurses through the given AST to find identifiers which are
265-
-- 'InstanceValBind's.
266-
findInstanceValBindIdentifiers :: HieAST a -> [Identifier]
267-
findInstanceValBindIdentifiers ast =
268-
let valBindIds = Map.keys
269-
. Map.filter (any isInstanceValBind . identInfo)
270-
$ getNodeIds ast
271-
in valBindIds <> concatMap findInstanceValBindIdentifiers (nodeChildren ast)
272-
273-
ghostSpan :: RealSrcSpan
274-
ghostSpan = realSrcLocSpan $ mkRealSrcLoc (fsLit "<haskell-language-sever>") 1 1
275-
276-
containRange :: Range -> SrcSpan -> Bool
277-
containRange range x = isInsideSrcSpan (range ^. J.start) x || isInsideSrcSpan (range ^. J.end) x
278-
279-
isClassNodeIdentifier :: IdentifierDetails a -> Bool
280-
isClassNodeIdentifier ident = (isNothing . identType) ident && Use `Set.member` identInfo ident
281-
282-
isClassMethodWarning :: T.Text -> Bool
283-
isClassMethodWarning = T.isPrefixOf "• No explicit implementation for"
284-
285-
isInstanceValBind :: ContextInfo -> Bool
286-
isInstanceValBind (ValBind InstanceBind _ _) = True
287-
isInstanceValBind _ = False
288-
289-
minDefToMethodGroups :: BooleanFormula Name -> [[T.Text]]
290-
minDefToMethodGroups = go
291-
where
292-
go (Var mn) = [[T.pack . occNameString . occName $ mn]]
293-
go (Or ms) = concatMap (go . unLoc) ms
294-
go (And ms) = foldr (liftA2 (<>)) [[]] (fmap (go . unLoc) ms)
295-
go (Parens m) = go (unLoc m)

0 commit comments

Comments
 (0)