Skip to content

Commit 2b49d9d

Browse files
authored
Give plugins descriptions, include versions of key dependencies (#3903)
* Plugins have descriptions * Plugins based on external tools report the version they are built with * Sort plugins
1 parent 7b4f54d commit 2b49d9d

File tree

39 files changed

+105
-62
lines changed

39 files changed

+105
-62
lines changed

exe/Main.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -13,19 +13,19 @@ import Data.Function ((&))
1313
import Data.Functor ((<&>))
1414
import Data.Maybe (catMaybes)
1515
import Data.Text (Text)
16-
import Ide.Logger (Doc, Priority (Error, Info),
16+
import qualified HlsPlugins as Plugins
17+
import Ide.Arguments (Arguments (..),
18+
GhcideArguments (..),
19+
getArguments)
20+
import Ide.Logger (Doc, Priority (Error, Info),
1721
Recorder,
1822
WithPriority (WithPriority, priority),
1923
cfilter, cmapWithPrio,
2024
defaultLayoutOptions,
2125
layoutPretty, logWith,
2226
makeDefaultStderrRecorder,
2327
renderStrict, withFileRecorder)
24-
import qualified Ide.Logger as Logger
25-
import qualified HlsPlugins as Plugins
26-
import Ide.Arguments (Arguments (..),
27-
GhcideArguments (..),
28-
getArguments)
28+
import qualified Ide.Logger as Logger
2929
import Ide.Main (defaultMain)
3030
import qualified Ide.Main as IdeMain
3131
import Ide.PluginUtils (pluginDescToIdePlugins)
@@ -70,7 +70,7 @@ main = do
7070
])
7171
-- This plugin just installs a handler for the `initialized` notification, which then
7272
-- picks up the LSP environment and feeds it to our recorders
73-
let lspRecorderPlugin = (defaultPluginDescriptor "LSPRecorderCallback")
73+
let lspRecorderPlugin = (defaultPluginDescriptor "LSPRecorderCallback" "Internal plugin")
7474
{ pluginNotificationHandlers = mkPluginNotificationHandler LSP.SMethod_Initialized $ \_ _ _ _ -> do
7575
env <- LSP.getLspEnv
7676
liftIO $ (cb1 <> cb2) env

ghcide/exe/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -100,7 +100,7 @@ main = withTelemetryLogger $ \telemetryLogger -> do
100100
(lspMessageRecorder, cb2) <- Logger.withBacklog Logger.lspClientMessageRecorder
101101
-- This plugin just installs a handler for the `initialized` notification, which then
102102
-- picks up the LSP environment and feeds it to our recorders
103-
let lspRecorderPlugin = (defaultPluginDescriptor "LSPRecorderCallback")
103+
let lspRecorderPlugin = (defaultPluginDescriptor "LSPRecorderCallback" "Internal plugin")
104104
{ pluginNotificationHandlers = mkPluginNotificationHandler LSP.SMethod_Initialized $ \_ _ _ _ -> do
105105
env <- LSP.getLspEnv
106106
liftIO $ (cb1 <> cb2) env

ghcide/src/Development/IDE/LSP/Notifications.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,7 @@ whenUriFile :: Uri -> (NormalizedFilePath -> IO ()) -> IO ()
5454
whenUriFile uri act = whenJust (LSP.uriToFilePath uri) $ act . toNormalizedFilePath'
5555

5656
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
57-
descriptor recorder plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers = mconcat
57+
descriptor recorder plId = (defaultPluginDescriptor plId desc) { pluginNotificationHandlers = mconcat
5858
[ mkPluginNotificationHandler LSP.SMethod_TextDocumentDidOpen $
5959
\ide vfs _ (DidOpenTextDocumentParams TextDocumentItem{_uri,_version}) -> liftIO $ do
6060
atomically $ updatePositionMapping ide (VersionedTextDocumentIdentifier _uri _version) []
@@ -142,6 +142,8 @@ descriptor recorder plId = (defaultPluginDescriptor plId) { pluginNotificationHa
142142
-- (which restart the Shake build) run after everything else
143143
pluginPriority = ghcideNotificationsPluginPriority
144144
}
145+
where
146+
desc = "Handles basic notifications for ghcide"
145147

146148
ghcideNotificationsPluginPriority :: Natural
147149
ghcideNotificationsPluginPriority = defaultPluginPriority - 900

ghcide/src/Development/IDE/Plugin/Completions.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -71,13 +71,15 @@ ghcideCompletionsPluginPriority :: Natural
7171
ghcideCompletionsPluginPriority = defaultPluginPriority
7272

7373
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
74-
descriptor recorder plId = (defaultPluginDescriptor plId)
74+
descriptor recorder plId = (defaultPluginDescriptor plId desc)
7575
{ pluginRules = produceCompletions recorder
7676
, pluginHandlers = mkPluginHandler SMethod_TextDocumentCompletion getCompletionsLSP
7777
<> mkResolveHandler SMethod_CompletionItemResolve resolveCompletion
7878
, pluginConfigDescriptor = defaultConfigDescriptor {configCustomConfig = mkCustomConfig properties}
7979
, pluginPriority = ghcideCompletionsPluginPriority
8080
}
81+
where
82+
desc = "Provides Haskell completions"
8183

8284

8385
produceCompletions :: Recorder (WithPriority Log) -> Rules ()

ghcide/src/Development/IDE/Plugin/HLS/GhcIde.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ descriptors recorder =
4242
-- ---------------------------------------------------------------------
4343

4444
descriptor :: PluginId -> PluginDescriptor IdeState
45-
descriptor plId = (defaultPluginDescriptor plId)
45+
descriptor plId = (defaultPluginDescriptor plId desc)
4646
{ pluginHandlers = mkPluginHandler SMethod_TextDocumentHover hover'
4747
<> mkPluginHandler SMethod_TextDocumentDocumentSymbol moduleOutline
4848
<> mkPluginHandler SMethod_TextDocumentDefinition (\ide _ DefinitionParams{..} ->
@@ -56,6 +56,8 @@ descriptor plId = (defaultPluginDescriptor plId)
5656

5757
pluginConfigDescriptor = defaultConfigDescriptor
5858
}
59+
where
60+
desc = "Provides core IDE features for Haskell"
5961

6062
-- ---------------------------------------------------------------------
6163

ghcide/src/Development/IDE/Plugin/Test.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ newtype WaitForIdeRuleResult = WaitForIdeRuleResult { ideResultSuccess::Bool}
7777
deriving newtype (FromJSON, ToJSON)
7878

7979
plugin :: PluginDescriptor IdeState
80-
plugin = (defaultPluginDescriptor "test") {
80+
plugin = (defaultPluginDescriptor "test" "") {
8181
pluginHandlers = mkPluginHandler (SMethod_CustomMethod (Proxy @"test")) $ \st _ ->
8282
testRequestHandler' st
8383
}
@@ -166,7 +166,7 @@ blockCommandId :: Text
166166
blockCommandId = "ghcide.command.block"
167167

168168
blockCommandDescriptor :: PluginId -> PluginDescriptor state
169-
blockCommandDescriptor plId = (defaultPluginDescriptor plId) {
169+
blockCommandDescriptor plId = (defaultPluginDescriptor plId "") {
170170
pluginCommands = [PluginCommand (CommandId blockCommandId) "blocks forever" blockCommandHandler]
171171
}
172172

ghcide/src/Development/IDE/Plugin/TypeLenses.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -94,13 +94,15 @@ typeLensCommandId = "typesignature.add"
9494

9595
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
9696
descriptor recorder plId =
97-
(defaultPluginDescriptor plId)
97+
(defaultPluginDescriptor plId desc)
9898
{ pluginHandlers = mkPluginHandler SMethod_TextDocumentCodeLens codeLensProvider
9999
<> mkResolveHandler SMethod_CodeLensResolve codeLensResolveProvider
100100
, pluginCommands = [PluginCommand (CommandId typeLensCommandId) "adds a signature" commandHandler]
101101
, pluginRules = rules recorder
102102
, pluginConfigDescriptor = defaultConfigDescriptor {configCustomConfig = mkCustomConfig properties}
103103
}
104+
where
105+
desc = "Provides code lenses type signatures"
104106

105107
properties :: Properties '[ 'PropertyKey "mode" (TEnum Mode)]
106108
properties = emptyProperties

ghcide/test/exe/ExceptionTests.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ tests recorder logger = do
4141
[ testCase "PluginHandlers" $ do
4242
let pluginId = "plugin-handler-exception"
4343
plugins = pluginDescToIdePlugins $
44-
[ (defaultPluginDescriptor pluginId)
44+
[ (defaultPluginDescriptor pluginId "")
4545
{ pluginHandlers = mconcat
4646
[ mkPluginHandler SMethod_TextDocumentCodeLens $ \_ _ _-> do
4747
_ <- liftIO $ throwIO DivideByZero
@@ -62,7 +62,7 @@ tests recorder logger = do
6262
let pluginId = "command-exception"
6363
commandId = CommandId "exception"
6464
plugins = pluginDescToIdePlugins $
65-
[ (defaultPluginDescriptor pluginId)
65+
[ (defaultPluginDescriptor pluginId "")
6666
{ pluginCommands =
6767
[ PluginCommand commandId "Causes an exception" $ \_ (_::Int) -> do
6868
_ <- liftIO $ throwIO DivideByZero
@@ -84,7 +84,7 @@ tests recorder logger = do
8484
, testCase "Notification Handlers" $ do
8585
let pluginId = "notification-exception"
8686
plugins = pluginDescToIdePlugins $
87-
[ (defaultPluginDescriptor pluginId)
87+
[ (defaultPluginDescriptor pluginId "")
8888
{ pluginNotificationHandlers = mconcat
8989
[ mkPluginNotificationHandler SMethod_TextDocumentDidOpen $ \_ _ _ _ ->
9090
liftIO $ throwIO DivideByZero
@@ -137,7 +137,7 @@ pluginOrderTestCase recorder logger msg err1 err2 =
137137
testCase msg $ do
138138
let pluginId = "error-order-test"
139139
plugins = pluginDescToIdePlugins $
140-
[ (defaultPluginDescriptor pluginId)
140+
[ (defaultPluginDescriptor pluginId "")
141141
{ pluginHandlers = mconcat
142142
[ mkPluginHandler SMethod_TextDocumentCodeLens $ \_ _ _-> do
143143
throwError $ err1 "error test"

ghcide/test/exe/UnitTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,7 @@ tests recorder logger = do
8080
}
8181
| i <- [1..20]
8282
] ++ Ghcide.descriptors (cmapWithPrio LogGhcIde recorder)
83-
priorityPluginDescriptor i = (defaultPluginDescriptor $ fromString $ show i){pluginPriority = i}
83+
priorityPluginDescriptor i = (defaultPluginDescriptor (fromString $ show i) ""){pluginPriority = i}
8484

8585
testIde recorder (IDE.testing (cmapWithPrio LogIDEMain recorder) logger plugins) $ do
8686
_ <- createDoc "A.hs" "haskell" "module A where"

hls-plugin-api/src/Ide/Types.hs

Lines changed: 16 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@
2525
module Ide.Types
2626
( PluginDescriptor(..), defaultPluginDescriptor, defaultCabalPluginDescriptor
2727
, defaultPluginPriority
28+
, describePlugin
2829
, IdeCommand(..)
2930
, IdeMethod(..)
3031
, IdeNotification(..)
@@ -104,6 +105,7 @@ import Language.LSP.VFS
104105
import Numeric.Natural
105106
import OpenTelemetry.Eventlog
106107
import Options.Applicative (ParserInfo)
108+
import Prettyprinter as PP
107109
import System.FilePath
108110
import System.IO.Unsafe
109111
import Text.Regex.TDFA.Text ()
@@ -266,6 +268,7 @@ instance ToJSON PluginConfig where
266268

267269
data PluginDescriptor (ideState :: Type) =
268270
PluginDescriptor { pluginId :: !PluginId
271+
, pluginDescription :: !T.Text
269272
-- ^ Unique identifier of the plugin.
270273
, pluginPriority :: Natural
271274
-- ^ Plugin handlers are called in priority order, higher priority first
@@ -283,6 +286,13 @@ data PluginDescriptor (ideState :: Type) =
283286
-- The file extension must have a leading '.'.
284287
}
285288

289+
describePlugin :: PluginDescriptor c -> Doc ann
290+
describePlugin p =
291+
let
292+
PluginId pid = pluginId p
293+
pdesc = pluginDescription p
294+
in pretty pid <> ":" <> nest 4 (PP.line <> pretty pdesc)
295+
286296
-- | Check whether the given plugin descriptor is responsible for the file with the given path.
287297
-- Compares the file extension of the file at the given path with the file extension
288298
-- the plugin is responsible for.
@@ -894,10 +904,11 @@ defaultPluginPriority = 1000
894904
--
895905
-- and handlers will be enabled for files with the appropriate file
896906
-- extensions.
897-
defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState
898-
defaultPluginDescriptor plId =
907+
defaultPluginDescriptor :: PluginId -> T.Text -> PluginDescriptor ideState
908+
defaultPluginDescriptor plId desc =
899909
PluginDescriptor
900910
plId
911+
desc
901912
defaultPluginPriority
902913
mempty
903914
mempty
@@ -914,10 +925,11 @@ defaultPluginDescriptor plId =
914925
--
915926
-- Handles files with the following extensions:
916927
-- * @.cabal@
917-
defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState
918-
defaultCabalPluginDescriptor plId =
928+
defaultCabalPluginDescriptor :: PluginId -> T.Text -> PluginDescriptor ideState
929+
defaultCabalPluginDescriptor plId desc =
919930
PluginDescriptor
920931
plId
932+
desc
921933
defaultPluginPriority
922934
mempty
923935
mempty

0 commit comments

Comments
 (0)