1
1
{-# LANGUAGE GADTs #-}
2
+ {-# LANGUAGE LambdaCase #-}
2
3
{-# LANGUAGE OverloadedLists #-}
3
4
{-# LANGUAGE RecordWildCards #-}
4
5
{-# LANGUAGE ViewPatterns #-}
5
6
6
- module Ide.Plugin.Class.CodeAction where
7
+ module Ide.Plugin.Class.CodeAction (
8
+ addMethodPlaceholders ,
9
+ codeAction ,
10
+ ) where
7
11
12
+ import Control.Arrow ((>>>) )
8
13
import Control.Lens hiding (List , use )
9
14
import Control.Monad.Error.Class (MonadError (throwError ))
10
15
import Control.Monad.Extra
@@ -13,8 +18,6 @@ import Control.Monad.Trans.Class (lift)
13
18
import Control.Monad.Trans.Except (ExceptT )
14
19
import Control.Monad.Trans.Maybe
15
20
import Data.Aeson hiding (Null )
16
- import Data.Bifunctor (second )
17
- import Data.Either.Extra (rights )
18
21
import Data.List
19
22
import Data.List.Extra (nubOrdOn )
20
23
import qualified Data.Map.Strict as Map
@@ -23,11 +26,14 @@ import Data.Maybe (isNothing, listToMaybe,
23
26
import qualified Data.Set as Set
24
27
import qualified Data.Text as T
25
28
import Development.IDE
26
- import Development.IDE.Core.Compile (sourceTypecheck )
27
29
import Development.IDE.Core.FileStore (getVersionedTextDoc )
28
30
import Development.IDE.Core.PluginUtils
29
31
import Development.IDE.Core.PositionMapping (fromCurrentRange )
30
32
import Development.IDE.GHC.Compat
33
+ import Development.IDE.GHC.Compat.Error (TcRnMessage (.. ),
34
+ _TcRnMessage ,
35
+ stripTcRnMessageContext ,
36
+ msgEnvelopeErrorL )
31
37
import Development.IDE.GHC.Compat.Util
32
38
import Development.IDE.Spans.AtPoint (pointCommand )
33
39
import Ide.Plugin.Class.ExactPrint
@@ -80,23 +86,25 @@ addMethodPlaceholders _ state _ param@AddMinimalMethodsParams{..} = do
80
86
-- This implementation is ad-hoc in a sense that the diagnostic detection mechanism is
81
87
-- sensitive to the format of diagnostic messages from GHC.
82
88
codeAction :: Recorder (WithPriority Log ) -> PluginMethodHandler IdeState Method_TextDocumentCodeAction
83
- codeAction recorder state plId (CodeActionParams _ _ docId _ context ) = do
89
+ codeAction recorder state plId (CodeActionParams _ _ docId caRange _ ) = do
84
90
verTxtDocId <- liftIO $ runAction " classplugin.codeAction.getVersionedTextDoc" state $ getVersionedTextDoc docId
85
91
nfp <- getNormalizedFilePathE (verTxtDocId ^. L. uri)
86
- actions <- join <$> mapM (mkActions nfp verTxtDocId) methodDiags
87
- pure $ InL actions
92
+ activeDiagnosticsInRange (shakeExtras state) nfp caRange
93
+ >>= \ case
94
+ Nothing -> pure $ InL []
95
+ Just fileDiags -> do
96
+ actions <- join <$> mapM (mkActions nfp verTxtDocId) (methodDiags fileDiags)
97
+ pure $ InL actions
88
98
where
89
- diags = context ^. L. diagnostics
90
-
91
- ghcDiags = filter (\ d -> d ^. L. source == Just sourceTypecheck) diags
92
- methodDiags = filter (\ d -> isClassMethodWarning (d ^. L. message)) ghcDiags
99
+ methodDiags fileDiags =
100
+ mapMaybe (\ d -> (d,) <$> isClassMethodWarning (d ^. fdStructuredMessageL)) fileDiags
93
101
94
102
mkActions
95
103
:: NormalizedFilePath
96
104
-> VersionedTextDocumentIdentifier
97
- -> Diagnostic
105
+ -> ( FileDiagnostic , ClassMinimalDef )
98
106
-> ExceptT PluginError (HandlerM Ide.Plugin.Config. Config ) [Command |? CodeAction ]
99
- mkActions docPath verTxtDocId diag = do
107
+ mkActions docPath verTxtDocId ( diag, classMinDef) = do
100
108
(HAR {hieAst = ast}, pmap) <- runActionE " classplugin.findClassIdentifier.GetHieAst" state
101
109
$ useWithStaleE GetHieAst docPath
102
110
instancePosition <- handleMaybe (PluginInvalidUserState " fromCurrentRange" ) $
@@ -108,21 +116,19 @@ codeAction recorder state plId (CodeActionParams _ _ docId _ context) = do
108
116
$ useE GetInstanceBindTypeSigs docPath
109
117
(tmrTypechecked -> gblEnv ) <- runActionE " classplugin.codeAction.TypeCheck" state $ useE TypeCheck docPath
110
118
(hscEnv -> hsc) <- runActionE " classplugin.codeAction.GhcSession" state $ useE GhcSession docPath
111
- implemented <- findImplementedMethods ast instancePosition
112
- logWith recorder Info (LogImplementedMethods cls implemented)
119
+ logWith recorder Debug (LogImplementedMethods cls classMinDef)
113
120
pure
114
121
$ concatMap mkAction
115
122
$ nubOrdOn snd
116
123
$ filter ((/=) mempty . snd )
117
- $ fmap (second (filter (\ (bind, _) -> bind `notElem` implemented)))
118
- $ mkMethodGroups hsc gblEnv range sigs cls
124
+ $ mkMethodGroups hsc gblEnv range sigs classMinDef
119
125
where
120
- range = diag ^. L. range
126
+ range = diag ^. fdLspDiagnosticL . L. range
121
127
122
- mkMethodGroups :: HscEnv -> TcGblEnv -> Range -> [InstanceBindTypeSig ] -> Class -> [MethodGroup ]
123
- 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]
124
130
where
125
- minimalDef = minDefToMethodGroups hsc gblEnv range sigs $ classMinimalDef cls
131
+ minimalDef = minDefToMethodGroups hsc gblEnv range sigs classMinDef
126
132
allClassMethods = (" all missing methods" , makeMethodDefinitions hsc gblEnv range sigs)
127
133
128
134
mkAction :: MethodGroup -> [Command |? CodeAction ]
@@ -163,25 +169,6 @@ codeAction recorder state plId (CodeActionParams _ _ docId _ context) = do
163
169
<=< nodeChildren
164
170
)
165
171
166
- findImplementedMethods
167
- :: HieASTs a
168
- -> Position
169
- -> ExceptT PluginError (HandlerM Ide.Plugin.Config. Config ) [T. Text ]
170
- findImplementedMethods asts instancePosition = do
171
- pure
172
- $ concat
173
- $ pointCommand asts instancePosition
174
- $ map (T. pack . getOccString) . rights . findInstanceValBindIdentifiers
175
-
176
- -- | Recurses through the given AST to find identifiers which are
177
- -- 'InstanceValBind's.
178
- findInstanceValBindIdentifiers :: HieAST a -> [Identifier ]
179
- findInstanceValBindIdentifiers ast =
180
- let valBindIds = Map. keys
181
- . Map. filter (any isInstanceValBind . identInfo)
182
- $ getNodeIds ast
183
- in valBindIds <> concatMap findInstanceValBindIdentifiers (nodeChildren ast)
184
-
185
172
findClassFromIdentifier docPath (Right name) = do
186
173
(hscEnv -> hscenv, _) <- runActionE " classplugin.findClassFromIdentifier.GhcSessionDeps" state
187
174
$ useWithStaleE GhcSessionDeps docPath
@@ -203,12 +190,15 @@ isClassNodeIdentifier :: Identifier -> IdentifierDetails a -> Bool
203
190
isClassNodeIdentifier (Right i) ident | ' C' : ' :' : _ <- unpackFS $ occNameFS $ occName i = (isNothing . identType) ident && Use `Set.member` identInfo ident
204
191
isClassNodeIdentifier _ _ = False
205
192
206
- isClassMethodWarning :: T. Text -> Bool
207
- isClassMethodWarning = T. isPrefixOf " • No explicit implementation for"
193
+ isClassMethodWarning :: StructuredMessage -> Maybe ClassMinimalDef
194
+ isClassMethodWarning message = case message ^? _SomeStructuredMessage . msgEnvelopeErrorL . _TcRnMessage of
195
+ Nothing -> Nothing
196
+ Just tcRnMessage -> isUnsatisfiedMinimalDefWarning tcRnMessage
208
197
209
- isInstanceValBind :: ContextInfo -> Bool
210
- isInstanceValBind (ValBind InstanceBind _ _) = True
211
- isInstanceValBind _ = False
198
+ isUnsatisfiedMinimalDefWarning :: TcRnMessage -> Maybe ClassMinimalDef
199
+ isUnsatisfiedMinimalDefWarning = stripTcRnMessageContext >>> \ case
200
+ TcRnUnsatisfiedMinimalDef classMinDef -> Just classMinDef
201
+ _ -> Nothing
212
202
213
203
type MethodSignature = T. Text
214
204
type MethodName = T. Text
0 commit comments