Skip to content

Commit 9d2b79d

Browse files
committed
Improve documentation for plugins
1 parent 257bb3e commit 9d2b79d

File tree

1 file changed

+105
-35
lines changed

1 file changed

+105
-35
lines changed

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

+105-35
Original file line numberDiff line numberDiff line change
@@ -112,6 +112,7 @@ instance Show (IdeCommand st) where show _ = "<ide command>"
112112

113113
data PluginDescriptor (ideState :: *) =
114114
PluginDescriptor { pluginId :: !PluginId
115+
-- ^ Unique identifier of the plugin.
115116
, pluginRules :: !(Rules ())
116117
, pluginCommands :: ![PluginCommand ideState]
117118
, pluginHandlers :: PluginHandlers ideState
@@ -126,11 +127,23 @@ data PluginDescriptor (ideState :: *) =
126127
-- The file extension must have a leading '.'.
127128
}
128129

130+
-- | Check whether the given plugin descriptor is responsible for the file with the given path.
131+
-- Compares the file extension of the file at the given path with the file extension
132+
-- the plugin is responsible for.
133+
pluginResponsible :: Uri -> PluginDescriptor c -> Bool
134+
pluginResponsible uri pluginDesc
135+
| Just fp <- mfp
136+
, T.pack (takeExtension fp) `elem` pluginFileType pluginDesc = True
137+
| otherwise = False
138+
where
139+
mfp = uriToFilePath uri
140+
129141
-- | An existential wrapper of 'Properties'
130142
data CustomConfig = forall r. CustomConfig (Properties r)
131143

132144
-- | Describes the configuration a plugin.
133145
-- A plugin may be configurable in such form:
146+
--
134147
-- @
135148
-- {
136149
-- "plugin-id": {
@@ -143,6 +156,7 @@ data CustomConfig = forall r. CustomConfig (Properties r)
143156
-- }
144157
-- }
145158
-- @
159+
--
146160
-- @globalOn@, @codeActionsOn@, and @codeLensOn@ etc. are called generic configs,
147161
-- which can be inferred from handlers registered by the plugin.
148162
-- @config@ is called custom config, which is defined using 'Properties'.
@@ -168,24 +182,65 @@ defaultConfigDescriptor = ConfigDescriptor True False (mkCustomConfig emptyPrope
168182
-- Only methods for which we know how to combine responses can be instances of 'PluginMethod'
169183
class HasTracing (MessageParams m) => PluginMethod (k :: MethodType) (m :: Method FromClient k) where
170184

171-
-- | Parse the configuration to check if this plugin is enabled
172-
pluginEnabled
173-
:: SMethod m
185+
-- | Parse the configuration to check if this plugin is enabled.
186+
-- Perform sanity checks on the message to see whether plugin is enabled
187+
-- for this message in particular.
188+
-- If a plugin is not enabled, its handlers, commands, etc... will not be
189+
-- run for the given message.
190+
--
191+
-- Semantically, this method described whether a Plugin is enabled configuration wise
192+
-- and is allowed to respond to the message. This might depend on the URI that is
193+
-- associated to the Message Parameters, but doesn't have to. There are requests
194+
-- with no associated URI that, consequentially, can't inspect the URI.
195+
--
196+
-- Common reason why a plugin might not be allowed to respond although it is enabled:
197+
-- * Plugin can not handle requests associated to the specific URI
198+
-- * Since the implementation of [cabal plugins](https://github.com/haskell/haskell-language-server/issues/2940)
199+
-- HLS knows plugins specific for Haskell and specific for [Cabal file descriptions](https://cabal.readthedocs.io/en/3.6/cabal-package.html)
200+
--
201+
-- Strictly speaking, we are conflating two concepts here:
202+
-- * Dynamically enabled (e.g. enabled on a per-message basis)
203+
-- * Statically enabled (e.g. by configuration in the lsp-client)
204+
-- * Strictly speaking, this might also change dynamically
205+
--
206+
-- But there is no use to split it up currently into two different methods for now.
207+
pluginEnabled
208+
:: SMethod m
209+
-- ^ Method type.
174210
-> MessageParams m
175-
-- ^ Whether a plugin is enabled might depend on the message parameters
211+
-- ^ Whether a plugin is enabled might depend on the message parameters
176212
-- eg 'pluginFileType' specifies what file extension a plugin is allowed to handle
177-
-> PluginDescriptor c
178-
-> Config
213+
-> PluginDescriptor c
214+
-- ^ Contains meta information such as PluginId and what file types this
215+
-- plugin is able to handle.
216+
-> Config
217+
-- ^ Generic config description, expected to hold 'PluginConfig' configuration
218+
-- for this plugin
179219
-> Bool
220+
-- ^ Is this plugin enabled and allowed to respond to the given request
221+
-- with the given parameters?
180222

181223
default pluginEnabled :: (HasTextDocument (MessageParams m) doc, HasUri doc Uri)
182224
=> SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
183225
pluginEnabled _ params desc conf = pluginResponsible uri desc && plcGlobalOn (configForPlugin conf (pluginId desc))
184226
where
185227
uri = params ^. J.textDocument . J.uri
186228

229+
-- ---------------------------------------------------------------------
230+
-- Plugin Requests
231+
-- ---------------------------------------------------------------------
232+
187233
class PluginMethod Request m => PluginRequestMethod (m :: Method FromClient Request) where
188-
-- | How to combine responses from different plugins
234+
-- | How to combine responses from different plugins.
235+
--
236+
-- For example, for Hover requests, we might have multiple producers of
237+
-- Hover information, we do not want to decide which one to display to the user
238+
-- but allow here to define how to merge two hover request responses into one
239+
-- glorious hover box.
240+
--
241+
-- However, sometimes only one handler of a request can realistically exist,
242+
-- such as TextDocumentFormatting, it is safe to just unconditionally report
243+
-- back one arbitrary result (arbitrary since it should only be one anyway).
189244
combineResponses
190245
:: SMethod m
191246
-> Config -- ^ IDE Configuration
@@ -197,7 +252,6 @@ class PluginMethod Request m => PluginRequestMethod (m :: Method FromClient Requ
197252
=> SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m
198253
combineResponses _method _config _caps _params = sconcat
199254

200-
201255
instance PluginMethod Request TextDocumentCodeAction where
202256
pluginEnabled _ msgParams pluginDesc config =
203257
pluginResponsible uri pluginDesc && pluginEnabledConfig plcCodeActionsOn (pluginId pluginDesc) config
@@ -231,17 +285,6 @@ instance PluginRequestMethod TextDocumentCodeAction where
231285
, Just caKind <- ca ^. kind = any (\k -> k `codeActionKindSubsumes` caKind) allowed
232286
| otherwise = False
233287

234-
-- | Check whether the given plugin descriptor is responsible for the file with the given path.
235-
-- Compares the file extension of the file at the given path with the file extension
236-
-- the plugin is responsible for.
237-
pluginResponsible :: Uri -> PluginDescriptor c -> Bool
238-
pluginResponsible uri pluginDesc
239-
| Just fp <- mfp
240-
, T.pack (takeExtension fp) `elem` pluginFileType pluginDesc = True
241-
| otherwise = False
242-
where
243-
mfp = uriToFilePath uri
244-
245288
instance PluginMethod Request TextDocumentDefinition where
246289
pluginEnabled _ msgParams pluginDesc _ =
247290
pluginResponsible uri pluginDesc
@@ -267,34 +310,34 @@ instance PluginMethod Request TextDocumentReferences where
267310
uri = msgParams ^. J.textDocument . J.uri
268311

269312
instance PluginMethod Request WorkspaceSymbol where
313+
-- Unconditionally enabled, but should it really be?
270314
pluginEnabled _ _ _ _ = True
271315

272316
instance PluginMethod Request TextDocumentCodeLens where
273-
pluginEnabled _ msgParams pluginDesc config =
274-
pluginResponsible uri pluginDesc
317+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
275318
&& pluginEnabledConfig plcCodeLensOn (pluginId pluginDesc) config
276319
where
277320
uri = msgParams ^. J.textDocument . J.uri
278321

279322
instance PluginMethod Request TextDocumentRename where
280-
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
323+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
281324
&& pluginEnabledConfig plcRenameOn (pluginId pluginDesc) config
282325
where
283326
uri = msgParams ^. J.textDocument . J.uri
284327
instance PluginMethod Request TextDocumentHover where
285-
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
328+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
286329
&& pluginEnabledConfig plcHoverOn (pluginId pluginDesc) config
287330
where
288331
uri = msgParams ^. J.textDocument . J.uri
289332

290333
instance PluginMethod Request TextDocumentDocumentSymbol where
291-
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
334+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
292335
&& pluginEnabledConfig plcSymbolsOn (pluginId pluginDesc) config
293336
where
294337
uri = msgParams ^. J.textDocument . J.uri
295338

296339
instance PluginMethod Request TextDocumentCompletion where
297-
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
340+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
298341
&& pluginEnabledConfig plcCompletionOn (pluginId pluginDesc) config
299342
where
300343
uri = msgParams ^. J.textDocument . J.uri
@@ -321,17 +364,20 @@ instance PluginMethod Request TextDocumentPrepareCallHierarchy where
321364
pid = pluginId pluginDesc
322365

323366
instance PluginMethod Request TextDocumentSelectionRange where
324-
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc && pluginEnabledConfig plcSelectionRangeOn pid conf
367+
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
368+
&& pluginEnabledConfig plcSelectionRangeOn pid conf
325369
where
326370
uri = msgParams ^. J.textDocument . J.uri
327371
pid = pluginId pluginDesc
328372

329373
instance PluginMethod Request CallHierarchyIncomingCalls where
374+
-- This method has no URI parameter, thus no call to 'pluginResponsible'
330375
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
331376
where
332377
pid = pluginId pluginDesc
333378

334379
instance PluginMethod Request CallHierarchyOutgoingCalls where
380+
-- This method has no URI parameter, thus no call to 'pluginResponsible'
335381
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
336382
where
337383
pid = pluginId pluginDesc
@@ -430,8 +476,13 @@ instance PluginRequestMethod CallHierarchyOutgoingCalls where
430476

431477
instance PluginRequestMethod CustomMethod where
432478
combineResponses _ _ _ _ (x :| _) = x
479+
480+
-- ---------------------------------------------------------------------
481+
-- Plugin Notifications
433482
-- ---------------------------------------------------------------------
434483

484+
-- | Plugin Notification methods. No specific methods at the moment, but
485+
-- might contain more in the future.
435486
class PluginMethod Notification m => PluginNotificationMethod (m :: Method FromClient Notification) where
436487

437488

@@ -443,27 +494,31 @@ instance PluginMethod Notification TextDocumentDidSave where
443494

444495
instance PluginMethod Notification TextDocumentDidClose where
445496

446-
447-
instance PluginNotificationMethod TextDocumentDidOpen where
448-
449-
instance PluginNotificationMethod TextDocumentDidChange where
450-
451-
instance PluginNotificationMethod TextDocumentDidSave where
452-
453-
instance PluginNotificationMethod TextDocumentDidClose where
454-
455497
instance PluginMethod Notification WorkspaceDidChangeWatchedFiles where
498+
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
456499
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
457500

458501
instance PluginMethod Notification WorkspaceDidChangeWorkspaceFolders where
502+
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
459503
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
460504

461505
instance PluginMethod Notification WorkspaceDidChangeConfiguration where
506+
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
462507
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
463508

464509
instance PluginMethod Notification Initialized where
510+
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
465511
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
466512

513+
514+
instance PluginNotificationMethod TextDocumentDidOpen where
515+
516+
instance PluginNotificationMethod TextDocumentDidChange where
517+
518+
instance PluginNotificationMethod TextDocumentDidSave where
519+
520+
instance PluginNotificationMethod TextDocumentDidClose where
521+
467522
instance PluginNotificationMethod WorkspaceDidChangeWatchedFiles where
468523

469524
instance PluginNotificationMethod WorkspaceDidChangeWorkspaceFolders where
@@ -540,6 +595,15 @@ mkPluginNotificationHandler m f
540595
where
541596
f' pid ide vfs = f ide vfs pid
542597

598+
-- | Set up a plugin descriptor, initialized with default values.
599+
-- This is plugin descriptor is prepared for @haskell@ files, such as
600+
--
601+
-- * @.hs@
602+
-- * @.lhs@
603+
-- * @.hs-boot@
604+
--
605+
-- and handlers will be enabled for files with the appropriate file
606+
-- extensions.
543607
defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState
544608
defaultPluginDescriptor plId =
545609
PluginDescriptor
@@ -553,6 +617,12 @@ defaultPluginDescriptor plId =
553617
Nothing
554618
[".hs", ".lhs", ".hs-boot"]
555619

620+
-- | Set up a plugin descriptor, initialized with default values.
621+
-- This is plugin descriptor is prepared for @.cabal@ files and as such,
622+
-- will only respond / run when @.cabal@ files are currently in scope.
623+
--
624+
-- Handles files with the following extensions:
625+
-- * @.cabal@
556626
defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState
557627
defaultCabalPluginDescriptor plId =
558628
PluginDescriptor

0 commit comments

Comments
 (0)