4
4
{-# LANGUAGE RecordWildCards #-}
5
5
{-# LANGUAGE ViewPatterns #-}
6
6
7
- module Ide.Plugin.Class.CodeAction where
7
+ module Ide.Plugin.Class.CodeAction (
8
+ addMethodPlaceholders ,
9
+ codeAction ,
10
+ ) where
8
11
9
12
import Control.Arrow ((>>>) )
10
13
import Control.Lens hiding (List , use )
@@ -15,8 +18,6 @@ import Control.Monad.Trans.Class (lift)
15
18
import Control.Monad.Trans.Except (ExceptT )
16
19
import Control.Monad.Trans.Maybe
17
20
import Data.Aeson hiding (Null )
18
- import Data.Bifunctor (second )
19
- import Data.Either.Extra (rights )
20
21
import Data.List
21
22
import Data.List.Extra (nubOrdOn )
22
23
import qualified Data.Map.Strict as Map
@@ -96,14 +97,14 @@ codeAction recorder state plId (CodeActionParams _ _ docId caRange _) = do
96
97
pure $ InL actions
97
98
where
98
99
methodDiags fileDiags =
99
- filter (\ d -> isClassMethodWarning (d ^. fdStructuredMessageL)) fileDiags
100
+ mapMaybe (\ d -> (d,) <$ > isClassMethodWarning (d ^. fdStructuredMessageL)) fileDiags
100
101
101
102
mkActions
102
103
:: NormalizedFilePath
103
104
-> VersionedTextDocumentIdentifier
104
- -> FileDiagnostic
105
+ -> ( FileDiagnostic , ClassMinimalDef )
105
106
-> ExceptT PluginError (HandlerM Ide.Plugin.Config. Config ) [Command |? CodeAction ]
106
- mkActions docPath verTxtDocId diag = do
107
+ mkActions docPath verTxtDocId ( diag, classMinDef) = do
107
108
(HAR {hieAst = ast}, pmap) <- runActionE " classplugin.findClassIdentifier.GetHieAst" state
108
109
$ useWithStaleE GetHieAst docPath
109
110
instancePosition <- handleMaybe (PluginInvalidUserState " fromCurrentRange" ) $
@@ -115,21 +116,19 @@ codeAction recorder state plId (CodeActionParams _ _ docId caRange _) = do
115
116
$ useE GetInstanceBindTypeSigs docPath
116
117
(tmrTypechecked -> gblEnv ) <- runActionE " classplugin.codeAction.TypeCheck" state $ useE TypeCheck docPath
117
118
(hscEnv -> hsc) <- runActionE " classplugin.codeAction.GhcSession" state $ useE GhcSession docPath
118
- implemented <- findImplementedMethods ast instancePosition
119
- logWith recorder Info (LogImplementedMethods cls implemented)
119
+ logWith recorder Debug (LogImplementedMethods cls classMinDef)
120
120
pure
121
121
$ concatMap mkAction
122
122
$ nubOrdOn snd
123
123
$ filter ((/=) mempty . snd )
124
- $ fmap (second (filter (\ (bind, _) -> bind `notElem` implemented)))
125
- $ mkMethodGroups hsc gblEnv range sigs cls
124
+ $ mkMethodGroups hsc gblEnv range sigs classMinDef
126
125
where
127
126
range = diag ^. fdLspDiagnosticL . L. range
128
127
129
- mkMethodGroups :: HscEnv -> TcGblEnv -> Range -> [InstanceBindTypeSig ] -> Class -> [MethodGroup ]
130
- mkMethodGroups hsc gblEnv range sigs cls = minimalDef <> [allClassMethods]
128
+ mkMethodGroups :: HscEnv -> TcGblEnv -> Range -> [InstanceBindTypeSig ] -> ClassMinimalDef -> [MethodGroup ]
129
+ mkMethodGroups hsc gblEnv range sigs classMinDef = minimalDef <> [allClassMethods]
131
130
where
132
- minimalDef = minDefToMethodGroups hsc gblEnv range sigs $ classMinimalDef cls
131
+ minimalDef = minDefToMethodGroups hsc gblEnv range sigs classMinDef
133
132
allClassMethods = (" all missing methods" , makeMethodDefinitions hsc gblEnv range sigs)
134
133
135
134
mkAction :: MethodGroup -> [Command |? CodeAction ]
@@ -170,25 +169,6 @@ codeAction recorder state plId (CodeActionParams _ _ docId caRange _) = do
170
169
<=< nodeChildren
171
170
)
172
171
173
- findImplementedMethods
174
- :: HieASTs a
175
- -> Position
176
- -> ExceptT PluginError (HandlerM Ide.Plugin.Config. Config ) [T. Text ]
177
- findImplementedMethods asts instancePosition = do
178
- pure
179
- $ concat
180
- $ pointCommand asts instancePosition
181
- $ map (T. pack . getOccString) . rights . findInstanceValBindIdentifiers
182
-
183
- -- | Recurses through the given AST to find identifiers which are
184
- -- 'InstanceValBind's.
185
- findInstanceValBindIdentifiers :: HieAST a -> [Identifier ]
186
- findInstanceValBindIdentifiers ast =
187
- let valBindIds = Map. keys
188
- . Map. filter (any isInstanceValBind . identInfo)
189
- $ getNodeIds ast
190
- in valBindIds <> concatMap findInstanceValBindIdentifiers (nodeChildren ast)
191
-
192
172
findClassFromIdentifier docPath (Right name) = do
193
173
(hscEnv -> hscenv, _) <- runActionE " classplugin.findClassFromIdentifier.GhcSessionDeps" state
194
174
$ useWithStaleE GhcSessionDeps docPath
@@ -210,19 +190,15 @@ isClassNodeIdentifier :: Identifier -> IdentifierDetails a -> Bool
210
190
isClassNodeIdentifier (Right i) ident | ' C' : ' :' : _ <- unpackFS $ occNameFS $ occName i = (isNothing . identType) ident && Use `Set.member` identInfo ident
211
191
isClassNodeIdentifier _ _ = False
212
192
213
- isClassMethodWarning :: StructuredMessage -> Bool
193
+ isClassMethodWarning :: StructuredMessage -> Maybe ClassMinimalDef
214
194
isClassMethodWarning message = case message ^? _SomeStructuredMessage . msgEnvelopeErrorL . _TcRnMessage of
215
- Nothing -> False
216
- Just tcRnMessage -> isGhcClassMethodWarning tcRnMessage
217
-
218
- isGhcClassMethodWarning :: TcRnMessage -> Bool
219
- isGhcClassMethodWarning = flatTcRnMessage >>> \ case
220
- TcRnUnsatisfiedMinimalDef {} -> True
221
- _ -> False
195
+ Nothing -> Nothing
196
+ Just tcRnMessage -> isUnsatisfiedMinimalDefWarning tcRnMessage
222
197
223
- isInstanceValBind :: ContextInfo -> Bool
224
- isInstanceValBind (ValBind InstanceBind _ _) = True
225
- isInstanceValBind _ = False
198
+ isUnsatisfiedMinimalDefWarning :: TcRnMessage -> Maybe ClassMinimalDef
199
+ isUnsatisfiedMinimalDefWarning = flatTcRnMessage >>> \ case
200
+ TcRnUnsatisfiedMinimalDef classMinDef -> Just classMinDef
201
+ _ -> Nothing
226
202
227
203
type MethodSignature = T. Text
228
204
type MethodName = T. Text
0 commit comments