@@ -21,10 +21,11 @@ import Data.List
21
21
import qualified Data.Map.Strict as Map
22
22
import Data.Maybe
23
23
import qualified Data.Text as T
24
+ import qualified Data.Set as Set
24
25
import Development.IDE hiding (pluginHandlers )
25
26
import Development.IDE.Core.PositionMapping (fromCurrentRange ,
26
27
toCurrentRange )
27
- import Development.IDE.GHC.Compat
28
+ import Development.IDE.GHC.Compat as Compat hiding ( locA )
28
29
import Development.IDE.GHC.Compat.Util
29
30
import Development.IDE.Spans.AtPoint
30
31
import qualified GHC.Generics as Generics
@@ -38,6 +39,11 @@ import Language.LSP.Server
38
39
import Language.LSP.Types
39
40
import qualified Language.LSP.Types.Lens as J
40
41
42
+ #if MIN_VERSION_ghc(9,2,0)
43
+ import GHC.Hs (AnnsModule (AnnsModule ))
44
+ import GHC.Parser.Annotation
45
+ #endif
46
+
41
47
descriptor :: PluginId -> PluginDescriptor IdeState
42
48
descriptor plId = (defaultPluginDescriptor plId)
43
49
{ pluginCommands = commands
@@ -63,25 +69,78 @@ addMethodPlaceholders state AddMinimalMethodsParams{..} = do
63
69
medit <- liftIO $ runMaybeT $ do
64
70
docPath <- MaybeT . pure . uriToNormalizedFilePath $ toNormalizedUri uri
65
71
pm <- MaybeT . runAction " classplugin" state $ use GetParsedModule docPath
66
- let
67
- ps = pm_parsed_source pm
68
- anns = relativiseApiAnns ps (pm_annotations pm)
69
- old = T. pack $ exactPrint ps anns
70
-
71
72
(hsc_dflags . hscEnv -> df) <- MaybeT . runAction " classplugin" state $ use GhcSessionDeps docPath
72
- List (unzip -> (mAnns, mDecls)) <- MaybeT . pure $ traverse (makeMethodDecl df) methodGroup
73
- let
74
- (ps', (anns', _), _) = runTransform (mergeAnns (mergeAnnList mAnns) anns) (addMethodDecls ps mDecls)
75
- new = T. pack $ exactPrint ps' anns'
76
-
73
+ (old, new) <- makeEditText pm df
77
74
pure (workspaceEdit caps old new)
75
+
78
76
forM_ medit $ \ edit ->
79
77
sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing edit) (\ _ -> pure () )
80
78
pure (Right Null )
81
79
where
82
-
83
80
indent = 2
84
81
82
+ workspaceEdit caps old new
83
+ = diffText caps (uri, old) new IncludeDeletions
84
+
85
+ toMethodName n
86
+ | Just (h, _) <- T. uncons n
87
+ , not (isAlpha h || h == ' _' )
88
+ = " (" <> n <> " )"
89
+ | otherwise
90
+ = n
91
+
92
+ #if MIN_VERSION_ghc(9,2,0)
93
+ makeEditText pm df = do
94
+ List mDecls <- MaybeT . pure $ traverse (makeMethodDecl df) methodGroup
95
+ let ps = makeDeltaAst $ pm_parsed_source pm
96
+ old = T. pack $ exactPrint ps
97
+ (ps', _, _) = runTransform (addMethodDecls ps mDecls)
98
+ new = T. pack $ exactPrint ps'
99
+ pure (old, new)
100
+
101
+ makeMethodDecl df mName =
102
+ either (const Nothing ) Just . parseDecl df (T. unpack mName) . T. unpack
103
+ $ toMethodName mName <> " = _"
104
+
105
+ addMethodDecls ps mDecls = do
106
+ allDecls <- hsDecls ps
107
+ let (before, ((L l inst): after)) = break (containRange range . getLoc) allDecls
108
+ replaceDecls ps (before ++ (L l (addWhere inst)): (map newLine mDecls ++ after))
109
+ where
110
+ -- Add `where` keyword for `instance X where` if `where` is missing.
111
+ --
112
+ -- The `where` in ghc-9.2 is now stored in the instance declaration
113
+ -- directly. More precisely, giving an `HsDecl GhcPs`, we have:
114
+ -- InstD --> ClsInstD --> ClsInstDecl --> XCClsInstDecl --> (EpAnn [AddEpAnn], AnnSortKey),
115
+ -- here `AnnEpAnn` keeps the track of Anns.
116
+ --
117
+ -- See the link for the original definition:
118
+ -- https://hackage.haskell.org/package/ghc-9.2.1/docs/Language-Haskell-Syntax-Extension.html#t:XCClsInstDecl
119
+ addWhere (InstD xInstD (ClsInstD ext decl@ ClsInstDecl {.. })) =
120
+ let ((EpAnn entry anns comments), key) = cid_ext
121
+ in InstD xInstD (ClsInstD ext decl {
122
+ cid_ext = (EpAnn
123
+ entry
124
+ (AddEpAnn AnnWhere (EpaDelta (SameLine 1 ) [] ) : anns)
125
+ comments
126
+ , key)
127
+ })
128
+ addWhere decl = decl
129
+
130
+ newLine (L l e) =
131
+ let dp = deltaPos 1 (indent + 1 ) -- Not sure why there need one more space
132
+ in L (noAnnSrcSpanDP (locA l) dp <> l) e
133
+
134
+ #else
135
+ makeEditText pm df = do
136
+ List (unzip -> (mAnns, mDecls)) <- MaybeT . pure $ traverse (makeMethodDecl df) methodGroup
137
+ let ps = pm_parsed_source pm
138
+ anns = relativiseApiAnns ps (pm_annotations pm)
139
+ old = T. pack $ exactPrint ps anns
140
+ (ps', (anns', _), _) = runTransform (mergeAnns (mergeAnnList mAnns) anns) (addMethodDecls ps mDecls)
141
+ new = T. pack $ exactPrint ps' anns'
142
+ pure (old, new)
143
+
85
144
makeMethodDecl df mName =
86
145
case parseDecl df (T. unpack mName) . T. unpack $ toMethodName mName <> " = _" of
87
146
Right (ann, d) -> Just (setPrecedingLines d 1 indent ann, d)
@@ -112,16 +171,7 @@ addMethodPlaceholders state AddMinimalMethodsParams{..} = do
112
171
113
172
findInstDecl :: ParsedSource -> Transform (LHsDecl GhcPs )
114
173
findInstDecl ps = head . filter (containRange range . getLoc) <$> hsDecls ps
115
-
116
- workspaceEdit caps old new
117
- = diffText caps (uri, old) new IncludeDeletions
118
-
119
- toMethodName n
120
- | Just (h, _) <- T. uncons n
121
- , not (isAlpha h || h == ' _' )
122
- = " (" <> n <> " )"
123
- | otherwise
124
- = n
174
+ #endif
125
175
126
176
-- |
127
177
-- This implementation is ad-hoc in a sense that the diagnostic detection mechanism is
@@ -169,15 +219,9 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
169
219
pure
170
220
$ head . head
171
221
$ pointCommand hf (fromJust (fromCurrentRange pmap range) ^. J. start & J. character -~ 1 )
172
- #if !MIN_VERSION_ghc(9,0,0)
173
- ( (Map. keys . Map. filter isClassNodeIdentifier . nodeIdentifiers . nodeInfo)
222
+ ( (Map. keys . Map. filter isClassNodeIdentifier . Compat. getNodeIds)
174
223
<=< nodeChildren
175
224
)
176
- #else
177
- ( (Map. keys . Map. filter isClassNodeIdentifier . sourcedNodeIdents . sourcedNodeInfo)
178
- <=< nodeChildren
179
- )
180
- #endif
181
225
182
226
findClassFromIdentifier docPath (Right name) = do
183
227
(hscEnv -> hscenv, _) <- MaybeT . runAction " classplugin" state $ useWithStale GhcSessionDeps docPath
@@ -197,7 +241,7 @@ containRange :: Range -> SrcSpan -> Bool
197
241
containRange range x = isInsideSrcSpan (range ^. J. start) x || isInsideSrcSpan (range ^. J. end) x
198
242
199
243
isClassNodeIdentifier :: IdentifierDetails a -> Bool
200
- isClassNodeIdentifier = isNothing . identType
244
+ isClassNodeIdentifier ident = ( isNothing . identType) ident && Use `Set.member` (identInfo ident)
201
245
202
246
isClassMethodWarning :: T. Text -> Bool
203
247
isClassMethodWarning = T. isPrefixOf " • No explicit implementation for"
0 commit comments