Skip to content

Commit d15cdde

Browse files
committed
hls-class-plugin: Add logs
1 parent b45f599 commit d15cdde

File tree

2 files changed

+15
-6
lines changed

2 files changed

+15
-6
lines changed

exe/Plugins.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -160,7 +160,7 @@ idePlugins recorder includeExamples = pluginDescToIdePlugins allPlugins
160160
CallHierarchy.descriptor :
161161
#endif
162162
#if class
163-
Class.descriptor "class" :
163+
Class.descriptor pluginRecorder "class" :
164164
#endif
165165
#if haddockComments
166166
HaddockComments.descriptor "haddockComments" :

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

Lines changed: 14 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
{-# LANGUAGE RecordWildCards #-}
66
{-# LANGUAGE TypeFamilies #-}
77
{-# LANGUAGE ViewPatterns #-}
8+
{-# LANGUAGE LambdaCase #-}
89
module Ide.Plugin.Class
910
( descriptor
1011
) where
@@ -39,16 +40,23 @@ import Language.Haskell.GHC.ExactPrint.Utils (rs)
3940
import Language.LSP.Server
4041
import Language.LSP.Types
4142
import qualified Language.LSP.Types.Lens as J
43+
import qualified Development.IDE.Core.Shake as Shake
4244

4345
#if MIN_VERSION_ghc(9,2,0)
4446
import GHC.Hs (AnnsModule(AnnsModule))
4547
import GHC.Parser.Annotation
4648
#endif
4749

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)
5058
{ pluginCommands = commands
51-
, pluginHandlers = mkPluginHandler STextDocumentCodeAction codeAction
59+
, pluginHandlers = mkPluginHandler STextDocumentCodeAction (codeAction recorder)
5260
}
5361

5462
commands :: [PluginCommand IdeState]
@@ -177,8 +185,8 @@ addMethodPlaceholders state AddMinimalMethodsParams{..} = do
177185
-- |
178186
-- This implementation is ad-hoc in a sense that the diagnostic detection mechanism is
179187
-- 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
182190
docPath <- MaybeT . pure . uriToNormalizedFilePath $ toNormalizedUri uri
183191
actions <- join <$> mapM (mkActions docPath) methodDiags
184192
pure . Right . List $ actions
@@ -194,6 +202,7 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
194202
ident <- findClassIdentifier docPath range
195203
cls <- findClassFromIdentifier docPath ident
196204
implemented <- findImplementedMethods docPath range
205+
logWith recorder Info (Log $ "Implemented methods: " <> T.pack (show implemented))
197206
lift . traverse (mkAction . (\\ implemented)) . minDefToMethodGroups . classMinimalDef $ cls
198207
where
199208
range = diag ^. J.range

0 commit comments

Comments
 (0)