Skip to content

Commit 941b557

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

File tree

4 files changed

+40
-25
lines changed

4 files changed

+40
-25
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/hls-class-plugin.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,7 @@ test-suite tests
5656
build-depends:
5757
, base
5858
, filepath
59+
, ghcide
5960
, hls-class-plugin
6061
, hls-test-utils ^>=1.3
6162
, lens

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

Lines changed: 16 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,10 @@
55
{-# LANGUAGE RecordWildCards #-}
66
{-# LANGUAGE TypeFamilies #-}
77
{-# LANGUAGE ViewPatterns #-}
8+
{-# LANGUAGE LambdaCase #-}
89
module Ide.Plugin.Class
9-
( descriptor
10+
( descriptor,
11+
Log (..)
1012
) where
1113

1214
import Control.Applicative
@@ -39,16 +41,23 @@ import Language.Haskell.GHC.ExactPrint.Utils (rs)
3941
import Language.LSP.Server
4042
import Language.LSP.Types
4143
import qualified Language.LSP.Types.Lens as J
44+
import qualified Development.IDE.Core.Shake as Shake
4245

4346
#if MIN_VERSION_ghc(9,2,0)
4447
import GHC.Hs (AnnsModule(AnnsModule))
4548
import GHC.Parser.Annotation
4649
#endif
4750

48-
descriptor :: PluginId -> PluginDescriptor IdeState
49-
descriptor plId = (defaultPluginDescriptor plId)
51+
newtype Log = Log T.Text deriving Show
52+
53+
instance Pretty Log where
54+
pretty = \case
55+
Log log -> pretty log
56+
57+
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
58+
descriptor recorder plId = (defaultPluginDescriptor plId)
5059
{ pluginCommands = commands
51-
, pluginHandlers = mkPluginHandler STextDocumentCodeAction codeAction
60+
, pluginHandlers = mkPluginHandler STextDocumentCodeAction (codeAction recorder)
5261
}
5362

5463
commands :: [PluginCommand IdeState]
@@ -177,8 +186,8 @@ addMethodPlaceholders state AddMinimalMethodsParams{..} = do
177186
-- |
178187
-- This implementation is ad-hoc in a sense that the diagnostic detection mechanism is
179188
-- 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
189+
codeAction :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState TextDocumentCodeAction
190+
codeAction recorder state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fromMaybe errorResult) . runMaybeT $ do
182191
docPath <- MaybeT . pure . uriToNormalizedFilePath $ toNormalizedUri uri
183192
actions <- join <$> mapM (mkActions docPath) methodDiags
184193
pure . Right . List $ actions
@@ -194,6 +203,7 @@ codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fr
194203
ident <- findClassIdentifier docPath range
195204
cls <- findClassFromIdentifier docPath ident
196205
implemented <- findImplementedMethods docPath range
206+
logWith recorder Info (Log $ "Implemented methods: " <> T.pack (show implemented))
197207
lift . traverse (mkAction . (\\ implemented)) . minDefToMethodGroups . classMinimalDef $ cls
198208
where
199209
range = diag ^. J.range

plugins/hls-class-plugin/test/Main.hs

Lines changed: 22 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -14,18 +14,22 @@ import qualified Ide.Plugin.Class as Class
1414
import qualified Language.LSP.Types.Lens as J
1515
import System.FilePath
1616
import Test.Hls
17+
import Development.IDE.Types.Logger
18+
import Data.Functor.Contravariant (contramap)
1719

1820
main :: IO ()
19-
main = defaultTestRunner tests
21+
main = do
22+
recorder <- makeDefaultStderrRecorder Nothing Debug
23+
defaultTestRunner . tests $ contramap (fmap pretty) recorder
2024

21-
classPlugin :: PluginDescriptor IdeState
22-
classPlugin = Class.descriptor "class"
25+
classPlugin :: Recorder (WithPriority Class.Log) -> PluginDescriptor IdeState
26+
classPlugin recorder = Class.descriptor recorder "class"
2327

24-
tests :: TestTree
25-
tests = testGroup
28+
tests :: Recorder (WithPriority Class.Log) -> TestTree
29+
tests recorder = testGroup
2630
"class"
2731
[ testCase "Produces addMinimalMethodPlaceholders code actions for one instance" $ do
28-
runSessionWithServer classPlugin testDataDir $ do
32+
runSessionWithServer (classPlugin recorder) testDataDir $ do
2933
doc <- openDoc "T1.hs" "haskell"
3034
_ <- waitForDiagnosticsFromSource doc "typecheck"
3135
caResults <- getAllCodeActions doc
@@ -34,23 +38,23 @@ tests = testGroup
3438
[ Just "Add placeholders for '=='"
3539
, Just "Add placeholders for '/='"
3640
]
37-
, goldenWithClass "Creates a placeholder for '=='" "T1" "eq" $ \(eqAction:_) -> do
41+
, goldenWithClass recorder "Creates a placeholder for '=='" "T1" "eq" $ \(eqAction:_) -> do
3842
executeCodeAction eqAction
39-
, goldenWithClass "Creates a placeholder for '/='" "T1" "ne" $ \(_:neAction:_) -> do
43+
, goldenWithClass recorder "Creates a placeholder for '/='" "T1" "ne" $ \(_:neAction:_) -> do
4044
executeCodeAction neAction
41-
, goldenWithClass "Creates a placeholder for 'fmap'" "T2" "fmap" $ \(_:_:fmapAction:_) -> do
45+
, goldenWithClass recorder "Creates a placeholder for 'fmap'" "T2" "fmap" $ \(_:_:fmapAction:_) -> do
4246
executeCodeAction fmapAction
43-
, goldenWithClass "Creates a placeholder for multiple methods 1" "T3" "1" $ \(mmAction:_) -> do
47+
, goldenWithClass recorder "Creates a placeholder for multiple methods 1" "T3" "1" $ \(mmAction:_) -> do
4448
executeCodeAction mmAction
45-
, goldenWithClass "Creates a placeholder for multiple methods 2" "T3" "2" $ \(_:mmAction:_) -> do
49+
, goldenWithClass recorder "Creates a placeholder for multiple methods 2" "T3" "2" $ \(_:mmAction:_) -> do
4650
executeCodeAction mmAction
47-
, goldenWithClass "Creates a placeholder for a method starting with '_'" "T4" "" $ \(_fAction:_) -> do
51+
, goldenWithClass recorder "Creates a placeholder for a method starting with '_'" "T4" "" $ \(_fAction:_) -> do
4852
executeCodeAction _fAction
49-
, goldenWithClass "Creates a placeholder for '==' with extra lines" "T5" "" $ \(eqAction:_) -> do
53+
, goldenWithClass recorder "Creates a placeholder for '==' with extra lines" "T5" "" $ \(eqAction:_) -> do
5054
executeCodeAction eqAction
51-
, goldenWithClass "Creates a placeholder for only the unimplemented methods of multiple methods" "T6" "1" $ \(gAction:_) -> do
55+
, goldenWithClass recorder "Creates a placeholder for only the unimplemented methods of multiple methods" "T6" "1" $ \(gAction:_) -> do
5256
executeCodeAction gAction
53-
, goldenWithClass "Creates a placeholder for other two multiple methods" "T6" "2" $ \(_:ghAction:_) -> do
57+
, goldenWithClass recorder "Creates a placeholder for other two methods" "T6" "2" $ \(_:ghAction:_) -> do
5458
executeCodeAction ghAction
5559
]
5660

@@ -59,9 +63,9 @@ _CACodeAction = prism' InR $ \case
5963
InR action -> Just action
6064
_ -> Nothing
6165

62-
goldenWithClass :: TestName -> FilePath -> FilePath -> ([CodeAction] -> Session ()) -> TestTree
63-
goldenWithClass title path desc act =
64-
goldenWithHaskellDoc classPlugin title testDataDir path (desc <.> "expected") "hs" $ \doc -> do
66+
goldenWithClass :: Recorder (WithPriority Class.Log) -> TestName -> FilePath -> FilePath -> ([CodeAction] -> Session ()) -> TestTree
67+
goldenWithClass recorder title path desc act =
68+
goldenWithHaskellDoc (classPlugin recorder) title testDataDir path (desc <.> "expected") "hs" $ \doc -> do
6569
_ <- waitForDiagnosticsFromSource doc "typecheck"
6670
actions <- concatMap (^.. _CACodeAction) <$> getAllCodeActions doc
6771
act actions

0 commit comments

Comments
 (0)