Skip to content

Commit 53b903e

Browse files
Jana Chadtfendor
authored andcommitted
Introduce PluginMethod Typeclass hierarchy
The hierarchy looks as follows: PluginMethod (pluginEnabled) | ----------------------------------- | | PluginRequestMethod PluginNotificationMethod
1 parent fed7ad7 commit 53b903e

File tree

2 files changed

+135
-72
lines changed

2 files changed

+135
-72
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -218,7 +218,7 @@ extensibleNotificationPlugins recorder xs = mempty { P.pluginHandlers = handlers
218218
case cleanPluginInfo of
219219
Left _ -> pure ()
220220
Right pluginInfos -> do
221-
let fs = map snd $ filter (\((_, desc), _) -> pluginEnabled2 m params desc config) (zip pluginInfos fs')
221+
let fs = map snd $ filter (\((_, desc), _) -> pluginEnabled m params desc config) (zip pluginInfos fs')
222222
case nonEmpty fs of
223223
Nothing -> do
224224
logWith recorder Info LogNoEnabledPlugins

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

Lines changed: 134 additions & 71 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@
1717
{-# LANGUAGE TypeFamilies #-}
1818
{-# LANGUAGE UndecidableInstances #-}
1919
{-# LANGUAGE ViewPatterns #-}
20+
{-# LANGUAGE MultiParamTypeClasses #-}
2021

2122
module Ide.Types
2223
where
@@ -165,11 +166,25 @@ defaultConfigDescriptor = ConfigDescriptor True False (mkCustomConfig emptyPrope
165166
-- | Methods that can be handled by plugins.
166167
-- 'ExtraParams' captures any extra data the IDE passes to the handlers for this method
167168
-- Only methods for which we know how to combine responses can be instances of 'PluginMethod'
168-
class HasTracing (MessageParams m) => PluginMethod m where
169+
class HasTracing (MessageParams m) => PluginMethod (k :: MethodType) (m :: Method FromClient k) where
169170

170171
-- | Parse the configuration to check if this plugin is enabled
171-
pluginEnabled :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
172+
pluginEnabled
173+
:: SMethod m
174+
-> MessageParams m
175+
-- ^ Whether a plugin is enabled might depend on the message parameters
176+
-- eg 'pluginFileType' specifies what file extension a plugin is allowed to handle
177+
-> PluginDescriptor c
178+
-> Config
179+
-> Bool
180+
181+
default pluginEnabled :: (HasTextDocument (MessageParams m) doc, HasUri doc Uri)
182+
=> SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
183+
pluginEnabled _ params desc conf = pluginResponsible uri desc && plcGlobalOn (configForPlugin conf (pluginId desc))
184+
where
185+
uri = params ^. J.textDocument . J.uri
172186

187+
class PluginMethod Request m => PluginRequestMethod (m :: Method FromClient Request) where
173188
-- | How to combine responses from different plugins
174189
combineResponses
175190
:: SMethod m
@@ -182,11 +197,14 @@ class HasTracing (MessageParams m) => PluginMethod m where
182197
=> SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m
183198
combineResponses _method _config _caps _params = sconcat
184199

185-
instance PluginMethod TextDocumentCodeAction where
200+
201+
instance PluginMethod Request TextDocumentCodeAction where
186202
pluginEnabled _ msgParams pluginDesc config =
187203
pluginResponsible uri pluginDesc && pluginEnabledConfig plcCodeActionsOn (pluginId pluginDesc) config
188204
where
189205
uri = msgParams ^. J.textDocument . J.uri
206+
207+
instance PluginRequestMethod TextDocumentCodeAction where
190208
combineResponses _method _config (ClientCapabilities _ textDocCaps _ _ _) (CodeActionParams _ _ _ _ context) resps =
191209
fmap compat $ List $ filter wasRequested $ (\(List x) -> x) $ sconcat resps
192210
where
@@ -243,64 +261,129 @@ pluginResponsible uri pluginDesc
243261
where
244262
mfp = uriToFilePath uri
245263

246-
instance PluginMethod TextDocumentDefinition where
264+
instance PluginMethod Request TextDocumentDefinition where
247265
pluginEnabled _ msgParams pluginDesc _ =
248266
pluginResponsible uri pluginDesc
249267
where
250268
uri = msgParams ^. J.textDocument . J.uri
251-
combineResponses _ _ _ _ (x :| _) = x
252269

253-
instance PluginMethod TextDocumentTypeDefinition where
270+
instance PluginMethod Request TextDocumentTypeDefinition where
254271
pluginEnabled _ msgParams pluginDesc _ =
255272
pluginResponsible uri pluginDesc
256273
where
257274
uri = msgParams ^. J.textDocument . J.uri
258-
combineResponses _ _ _ _ (x :| _) = x
259275

260-
instance PluginMethod TextDocumentDocumentHighlight where
276+
instance PluginMethod Request TextDocumentDocumentHighlight where
261277
pluginEnabled _ msgParams pluginDesc _ =
262278
pluginResponsible uri pluginDesc
263279
where
264280
uri = msgParams ^. J.textDocument . J.uri
265281

266-
instance PluginMethod TextDocumentReferences where
282+
instance PluginMethod Request TextDocumentReferences where
267283
pluginEnabled _ msgParams pluginDesc _ =
268284
pluginResponsible uri pluginDesc
269285
where
270286
uri = msgParams ^. J.textDocument . J.uri
271287

272-
instance PluginMethod WorkspaceSymbol where
288+
instance PluginMethod Request WorkspaceSymbol where
273289
pluginEnabled _ _ _ _ = True
274290

275-
instance PluginMethod TextDocumentCodeLens where
291+
instance PluginMethod Request TextDocumentCodeLens where
276292
pluginEnabled _ msgParams pluginDesc config =
277293
pluginResponsible uri pluginDesc
278294
&& pluginEnabledConfig plcCodeLensOn (pluginId pluginDesc) config
279295
where
280296
uri = msgParams ^. J.textDocument . J.uri
281297

282-
instance PluginMethod TextDocumentRename where
298+
instance PluginMethod Request TextDocumentRename where
283299
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
284300
&& pluginEnabledConfig plcRenameOn (pluginId pluginDesc) config
285301
where
286302
uri = msgParams ^. J.textDocument . J.uri
287-
instance PluginMethod TextDocumentHover where
303+
instance PluginMethod Request TextDocumentHover where
288304
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
289305
&& pluginEnabledConfig plcHoverOn (pluginId pluginDesc) config
290306
where
291307
uri = msgParams ^. J.textDocument . J.uri
308+
309+
instance PluginMethod Request TextDocumentDocumentSymbol where
310+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
311+
&& pluginEnabledConfig plcSymbolsOn (pluginId pluginDesc) config
312+
where
313+
uri = msgParams ^. J.textDocument . J.uri
314+
315+
instance PluginMethod Request TextDocumentCompletion where
316+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
317+
&& pluginEnabledConfig plcCompletionOn (pluginId pluginDesc) config
318+
where
319+
uri = msgParams ^. J.textDocument . J.uri
320+
321+
instance PluginMethod Request TextDocumentFormatting where
322+
pluginEnabled STextDocumentFormatting msgParams pluginDesc conf =
323+
pluginResponsible uri pluginDesc && PluginId (formattingProvider conf) == pid
324+
where
325+
uri = msgParams ^. J.textDocument . J.uri
326+
pid = pluginId pluginDesc
327+
328+
instance PluginMethod Request TextDocumentRangeFormatting where
329+
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
330+
&& PluginId (formattingProvider conf) == pid
331+
where
332+
uri = msgParams ^. J.textDocument . J.uri
333+
pid = pluginId pluginDesc
334+
335+
instance PluginMethod Request TextDocumentPrepareCallHierarchy where
336+
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
337+
&& pluginEnabledConfig plcCallHierarchyOn pid conf
338+
where
339+
uri = msgParams ^. J.textDocument . J.uri
340+
pid = pluginId pluginDesc
341+
342+
instance PluginMethod Request TextDocumentSelectionRange where
343+
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc && pluginEnabledConfig plcSelectionRangeOn pid conf
344+
where
345+
uri = msgParams ^. J.textDocument . J.uri
346+
pid = pluginId pluginDesc
347+
348+
instance PluginMethod Request CallHierarchyIncomingCalls where
349+
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
350+
where
351+
pid = pluginId pluginDesc
352+
353+
instance PluginMethod Request CallHierarchyOutgoingCalls where
354+
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
355+
where
356+
pid = pluginId pluginDesc
357+
358+
instance PluginMethod Request CustomMethod where
359+
pluginEnabled _ _ _ _ = True
360+
361+
---
362+
instance PluginRequestMethod TextDocumentDefinition where
363+
combineResponses _ _ _ _ (x :| _) = x
364+
365+
instance PluginRequestMethod TextDocumentTypeDefinition where
366+
combineResponses _ _ _ _ (x :| _) = x
367+
368+
instance PluginRequestMethod TextDocumentDocumentHighlight where
369+
370+
instance PluginRequestMethod TextDocumentReferences where
371+
372+
instance PluginRequestMethod WorkspaceSymbol where
373+
374+
instance PluginRequestMethod TextDocumentCodeLens where
375+
376+
instance PluginRequestMethod TextDocumentRename where
377+
378+
instance PluginRequestMethod TextDocumentHover where
292379
combineResponses _ _ _ _ (catMaybes . toList -> hs) = h
293380
where
294381
r = listToMaybe $ mapMaybe (^. range) hs
295382
h = case foldMap (^. contents) hs of
296383
HoverContentsMS (List []) -> Nothing
297384
hh -> Just $ Hover hh r
298385

299-
instance PluginMethod TextDocumentDocumentSymbol where
300-
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
301-
&& pluginEnabledConfig plcSymbolsOn (pluginId pluginDesc) config
302-
where
303-
uri = msgParams ^. J.textDocument . J.uri
386+
instance PluginRequestMethod TextDocumentDocumentSymbol where
304387
combineResponses _ _ (ClientCapabilities _ tdc _ _ _) params xs = res
305388
where
306389
uri' = params ^. textDocument . uri
@@ -321,11 +404,7 @@ instance PluginMethod TextDocumentDocumentSymbol where
321404
si = SymbolInformation name' (ds ^. kind) Nothing (ds ^. deprecated) loc parent
322405
in [si] <> children'
323406

324-
instance PluginMethod TextDocumentCompletion where
325-
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
326-
&& pluginEnabledConfig plcCompletionOn (pluginId pluginDesc) config
327-
where
328-
uri = msgParams ^. J.textDocument . J.uri
407+
instance PluginRequestMethod TextDocumentCompletion where
329408
combineResponses _ conf _ _ (toList -> xs) = snd $ consumeCompletionResponse limit $ combine xs
330409
where
331410
limit = maxCompletions conf
@@ -353,60 +432,36 @@ instance PluginMethod TextDocumentCompletion where
353432
consumeCompletionResponse n (InL (List xx)) =
354433
consumeCompletionResponse n (InR (CompletionList isCompleteResponse (List xx)))
355434

356-
instance PluginMethod TextDocumentFormatting where
357-
pluginEnabled STextDocumentFormatting msgParams pluginDesc conf =
358-
pluginResponsible uri pluginDesc && PluginId (formattingProvider conf) == pid
359-
where
360-
uri = msgParams ^. J.textDocument . J.uri
361-
pid = pluginId pluginDesc
362-
combineResponses _ _ _ _ x = sconcat x
363-
435+
instance PluginRequestMethod TextDocumentFormatting where
436+
combineResponses _ _ _ _ (x :| _) = x
364437

365-
instance PluginMethod TextDocumentRangeFormatting where
366-
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
367-
&& PluginId (formattingProvider conf) == pid
368-
where
369-
uri = msgParams ^. J.textDocument . J.uri
370-
pid = pluginId pluginDesc
438+
instance PluginRequestMethod TextDocumentRangeFormatting where
371439
combineResponses _ _ _ _ (x :| _) = x
372440

373-
instance PluginMethod TextDocumentPrepareCallHierarchy where
374-
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
375-
&& pluginEnabledConfig plcCallHierarchyOn pid conf
376-
where
377-
uri = msgParams ^. J.textDocument . J.uri
378-
pid = pluginId pluginDesc
441+
instance PluginRequestMethod TextDocumentPrepareCallHierarchy where
379442

380-
instance PluginMethod TextDocumentSelectionRange where
381-
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcSelectionRangeOn pid conf
382-
where
383-
pid = pluginId pluginDesc
443+
instance PluginRequestMethod TextDocumentSelectionRange where
384444
combineResponses _ _ _ _ (x :| _) = x
385445

386-
instance PluginMethod CallHierarchyIncomingCalls where
387-
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
388-
where
389-
pid = pluginId pluginDesc
446+
instance PluginRequestMethod CallHierarchyIncomingCalls where
390447

391-
instance PluginMethod CallHierarchyOutgoingCalls where
392-
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
393-
where
394-
pid = pluginId pluginDesc
448+
instance PluginRequestMethod CallHierarchyOutgoingCalls where
395449

396-
instance PluginMethod CustomMethod where
397-
pluginEnabled _ _ _ _ = True
450+
instance PluginRequestMethod CustomMethod where
398451
combineResponses _ _ _ _ (x :| _) = x
399-
400452
-- ---------------------------------------------------------------------
401453

402-
class HasTracing (MessageParams m) => PluginNotificationMethod (m :: Method FromClient Notification) where
403-
pluginEnabled2 :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
454+
class PluginMethod Notification m => PluginNotificationMethod (m :: Method FromClient Notification) where
455+
456+
457+
instance PluginMethod Notification TextDocumentDidOpen where
458+
459+
instance PluginMethod Notification TextDocumentDidChange where
460+
461+
instance PluginMethod Notification TextDocumentDidSave where
462+
463+
instance PluginMethod Notification TextDocumentDidClose where
404464

405-
default pluginEnabled2 :: (HasTextDocument (MessageParams m) doc, HasUri doc Uri)
406-
=> SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
407-
pluginEnabled2 _ params desc conf = pluginResponsible uri desc && plcGlobalOn (configForPlugin conf (pluginId desc))
408-
where
409-
uri = params ^. J.textDocument . J.uri
410465

411466
instance PluginNotificationMethod TextDocumentDidOpen where
412467

@@ -416,22 +471,30 @@ instance PluginNotificationMethod TextDocumentDidSave where
416471

417472
instance PluginNotificationMethod TextDocumentDidClose where
418473

474+
instance PluginMethod Notification WorkspaceDidChangeWatchedFiles where
475+
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
476+
477+
instance PluginMethod Notification WorkspaceDidChangeWorkspaceFolders where
478+
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
479+
480+
instance PluginMethod Notification WorkspaceDidChangeConfiguration where
481+
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
482+
483+
instance PluginMethod Notification Initialized where
484+
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
485+
419486
instance PluginNotificationMethod WorkspaceDidChangeWatchedFiles where
420-
pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
421487

422488
instance PluginNotificationMethod WorkspaceDidChangeWorkspaceFolders where
423-
pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
424489

425490
instance PluginNotificationMethod WorkspaceDidChangeConfiguration where
426-
pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
427491

428492
instance PluginNotificationMethod Initialized where
429-
pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
430493

431494
-- ---------------------------------------------------------------------
432495

433496
-- | Methods which have a PluginMethod instance
434-
data IdeMethod (m :: Method FromClient Request) = PluginMethod m => IdeMethod (SMethod m)
497+
data IdeMethod (m :: Method FromClient Request) = PluginRequestMethod m => IdeMethod (SMethod m)
435498
instance GEq IdeMethod where
436499
geq (IdeMethod a) (IdeMethod b) = geq a b
437500
instance GCompare IdeMethod where
@@ -477,7 +540,7 @@ type PluginNotificationMethodHandler a m = a -> VFS -> PluginId -> MessageParams
477540

478541
-- | Make a handler for plugins with no extra data
479542
mkPluginHandler
480-
:: PluginMethod m
543+
:: PluginRequestMethod m
481544
=> SClientMethod m
482545
-> PluginMethodHandler ideState m
483546
-> PluginHandlers ideState

0 commit comments

Comments
 (0)