5
5
{-# LANGUAGE RecordWildCards #-}
6
6
{-# LANGUAGE TypeFamilies #-}
7
7
{-# LANGUAGE ViewPatterns #-}
8
+ {-# LANGUAGE LambdaCase #-}
8
9
module Ide.Plugin.Class
9
10
( descriptor
10
11
) where
@@ -39,16 +40,23 @@ import Language.Haskell.GHC.ExactPrint.Utils (rs)
39
40
import Language.LSP.Server
40
41
import Language.LSP.Types
41
42
import qualified Language.LSP.Types.Lens as J
43
+ import qualified Development.IDE.Core.Shake as Shake
42
44
43
45
#if MIN_VERSION_ghc(9,2,0)
44
46
import GHC.Hs (AnnsModule (AnnsModule ))
45
47
import GHC.Parser.Annotation
46
48
#endif
47
49
48
- descriptor :: PluginId -> PluginDescriptor IdeState
49
- descriptor plId = (defaultPluginDescriptor plId)
50
+ newtype Log = Log T. Text deriving Show
51
+
52
+ instance Pretty Log where
53
+ pretty = \ case
54
+ Log log -> pretty log
55
+
56
+ descriptor :: Recorder (WithPriority Log ) -> PluginId -> PluginDescriptor IdeState
57
+ descriptor recorder plId = (defaultPluginDescriptor plId)
50
58
{ pluginCommands = commands
51
- , pluginHandlers = mkPluginHandler STextDocumentCodeAction codeAction
59
+ , pluginHandlers = mkPluginHandler STextDocumentCodeAction ( codeAction recorder)
52
60
}
53
61
54
62
commands :: [PluginCommand IdeState ]
@@ -177,8 +185,8 @@ addMethodPlaceholders state AddMinimalMethodsParams{..} = do
177
185
-- |
178
186
-- This implementation is ad-hoc in a sense that the diagnostic detection mechanism is
179
187
-- sensitive to the format of diagnostic messages from GHC.
180
- codeAction :: PluginMethodHandler IdeState TextDocumentCodeAction
181
- codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fromMaybe errorResult) . runMaybeT $ do
188
+ codeAction :: Recorder ( WithPriority Log ) -> PluginMethodHandler IdeState TextDocumentCodeAction
189
+ codeAction recorder state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fromMaybe errorResult) . runMaybeT $ do
182
190
docPath <- MaybeT . pure . uriToNormalizedFilePath $ toNormalizedUri uri
183
191
actions <- join <$> mapM (mkActions docPath) methodDiags
184
192
pure . Right . List $ actions
@@ -194,6 +202,7 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
194
202
ident <- findClassIdentifier docPath range
195
203
cls <- findClassFromIdentifier docPath ident
196
204
implemented <- findImplementedMethods docPath range
205
+ logWith recorder Info (Log $ " Implemented methods: " <> T. pack (show implemented))
197
206
lift . traverse (mkAction . (\\ implemented)) . minDefToMethodGroups . classMinimalDef $ cls
198
207
where
199
208
range = diag ^. J. range
0 commit comments