Skip to content

Commit f4d5c24

Browse files
committed
Make hls-class-plugin use the structured messages
1 parent 75c6409 commit f4d5c24

File tree

2 files changed

+22
-46
lines changed

2 files changed

+22
-46
lines changed

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

Lines changed: 19 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,10 @@
44
{-# LANGUAGE RecordWildCards #-}
55
{-# LANGUAGE ViewPatterns #-}
66

7-
module Ide.Plugin.Class.CodeAction where
7+
module Ide.Plugin.Class.CodeAction (
8+
addMethodPlaceholders,
9+
codeAction,
10+
) where
811

912
import Control.Arrow ((>>>))
1013
import Control.Lens hiding (List, use)
@@ -15,8 +18,6 @@ import Control.Monad.Trans.Class (lift)
1518
import Control.Monad.Trans.Except (ExceptT)
1619
import Control.Monad.Trans.Maybe
1720
import Data.Aeson hiding (Null)
18-
import Data.Bifunctor (second)
19-
import Data.Either.Extra (rights)
2021
import Data.List
2122
import Data.List.Extra (nubOrdOn)
2223
import qualified Data.Map.Strict as Map
@@ -96,14 +97,14 @@ codeAction recorder state plId (CodeActionParams _ _ docId caRange _) = do
9697
pure $ InL actions
9798
where
9899
methodDiags fileDiags =
99-
filter (\d -> isClassMethodWarning (d ^. fdStructuredMessageL)) fileDiags
100+
mapMaybe (\d -> (d,) <$> isClassMethodWarning (d ^. fdStructuredMessageL)) fileDiags
100101

101102
mkActions
102103
:: NormalizedFilePath
103104
-> VersionedTextDocumentIdentifier
104-
-> FileDiagnostic
105+
-> (FileDiagnostic, ClassMinimalDef)
105106
-> ExceptT PluginError (HandlerM Ide.Plugin.Config.Config) [Command |? CodeAction]
106-
mkActions docPath verTxtDocId diag = do
107+
mkActions docPath verTxtDocId (diag, classMinDef) = do
107108
(HAR {hieAst = ast}, pmap) <- runActionE "classplugin.findClassIdentifier.GetHieAst" state
108109
$ useWithStaleE GetHieAst docPath
109110
instancePosition <- handleMaybe (PluginInvalidUserState "fromCurrentRange") $
@@ -115,21 +116,19 @@ codeAction recorder state plId (CodeActionParams _ _ docId caRange _) = do
115116
$ useE GetInstanceBindTypeSigs docPath
116117
(tmrTypechecked -> gblEnv ) <- runActionE "classplugin.codeAction.TypeCheck" state $ useE TypeCheck docPath
117118
(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)
120120
pure
121121
$ concatMap mkAction
122122
$ nubOrdOn snd
123123
$ 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
126125
where
127126
range = diag ^. fdLspDiagnosticL . L.range
128127

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]
131130
where
132-
minimalDef = minDefToMethodGroups hsc gblEnv range sigs $ classMinimalDef cls
131+
minimalDef = minDefToMethodGroups hsc gblEnv range sigs classMinDef
133132
allClassMethods = ("all missing methods", makeMethodDefinitions hsc gblEnv range sigs)
134133

135134
mkAction :: MethodGroup -> [Command |? CodeAction]
@@ -170,25 +169,6 @@ codeAction recorder state plId (CodeActionParams _ _ docId caRange _) = do
170169
<=< nodeChildren
171170
)
172171

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-
192172
findClassFromIdentifier docPath (Right name) = do
193173
(hscEnv -> hscenv, _) <- runActionE "classplugin.findClassFromIdentifier.GhcSessionDeps" state
194174
$ useWithStaleE GhcSessionDeps docPath
@@ -210,19 +190,15 @@ isClassNodeIdentifier :: Identifier -> IdentifierDetails a -> Bool
210190
isClassNodeIdentifier (Right i) ident | 'C':':':_ <- unpackFS $ occNameFS $ occName i = (isNothing . identType) ident && Use `Set.member` identInfo ident
211191
isClassNodeIdentifier _ _ = False
212192

213-
isClassMethodWarning :: StructuredMessage -> Bool
193+
isClassMethodWarning :: StructuredMessage -> Maybe ClassMinimalDef
214194
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
222197

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
226202

227203
type MethodSignature = T.Text
228204
type MethodName = T.Text

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -112,15 +112,15 @@ instance NFData InstanceBindLensResult where
112112
type instance RuleResult GetInstanceBindLens = InstanceBindLensResult
113113

114114
data Log
115-
= LogImplementedMethods Class [T.Text]
115+
= LogImplementedMethods Class ClassMinimalDef
116116
| LogShake Shake.Log
117117

118118
instance Pretty Log where
119119
pretty = \case
120120
LogImplementedMethods cls methods ->
121-
pretty ("Detected implemented methods for class" :: String)
121+
pretty ("The following methods are missing" :: String)
122122
<+> pretty (show (getOccString cls) <> ":") -- 'show' is used here to add quotes around the class name
123-
<+> pretty methods
123+
<+> pretty (showSDocUnsafe $ ppr methods)
124124
LogShake log -> pretty log
125125

126126
data BindInfo = BindInfo

0 commit comments

Comments
 (0)