Skip to content

Commit e95a904

Browse files
author
Jana Chadt
committed
Introduce PluginMethod Typeclass hierarchy
The hierarchy looks as follows: PluginMethod (pluginEnabled) | ----------------------------------- | | PluginRequestMethod PluginNotificationMethod
1 parent 4b0d636 commit e95a904

File tree

3 files changed

+126
-71
lines changed

3 files changed

+126
-71
lines changed

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

+1-1
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ module Development.IDE.LSP.Server
1818
import Control.Monad.Reader
1919
import Development.IDE.Core.Shake
2020
import Development.IDE.Core.Tracing
21-
import Ide.Types (HasTracing, traceWithSpan)
21+
import Ide.Types (HasTracing, traceWithSpan, PluginRequestMethod, PluginNotificationMethod)
2222
import Language.LSP.Server (Handlers, LspM)
2323
import qualified Language.LSP.Server as LSP
2424
import Language.LSP.Types

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

+1-1
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

+124-69
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
@@ -161,11 +162,18 @@ defaultConfigDescriptor = ConfigDescriptor True False (mkCustomConfig emptyPrope
161162
-- | Methods that can be handled by plugins.
162163
-- 'ExtraParams' captures any extra data the IDE passes to the handlers for this method
163164
-- Only methods for which we know how to combine responses can be instances of 'PluginMethod'
164-
class HasTracing (MessageParams m) => PluginMethod m where
165+
class HasTracing (MessageParams m) => PluginMethod (k :: MethodType) (m :: Method FromClient k) where
165166

166167
-- | Parse the configuration to check if this plugin is enabled
167168
pluginEnabled :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
168169

170+
default pluginEnabled :: (HasTextDocument (MessageParams m) doc, HasUri doc Uri)
171+
=> SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
172+
pluginEnabled _ params desc conf = pluginResponsible uri desc && plcGlobalOn (configForPlugin conf (pluginId desc))
173+
where
174+
uri = params ^. J.textDocument . J.uri
175+
176+
class PluginMethod Request m => PluginRequestMethod (m :: Method FromClient Request) where
169177
-- | How to combine responses from different plugins
170178
combineResponses
171179
:: SMethod m
@@ -178,11 +186,14 @@ class HasTracing (MessageParams m) => PluginMethod m where
178186
=> SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m
179187
combineResponses _method _config _caps _params = sconcat
180188

181-
instance PluginMethod TextDocumentCodeAction where
189+
190+
instance PluginMethod Request TextDocumentCodeAction where
182191
pluginEnabled _ msgParams pluginDesc config =
183192
pluginResponsible uri pluginDesc && pluginEnabledConfig plcCodeActionsOn (pluginId pluginDesc) config
184193
where
185194
uri = msgParams ^. J.textDocument . J.uri
195+
196+
instance PluginRequestMethod TextDocumentCodeAction where
186197
combineResponses _method _config (ClientCapabilities _ textDocCaps _ _ _) (CodeActionParams _ _ _ _ context) resps =
187198
fmap compat $ List $ filter wasRequested $ (\(List x) -> x) $ sconcat resps
188199
where
@@ -217,64 +228,128 @@ pluginResponsible uri pluginDesc
217228
where
218229
mfp = uriToFilePath uri
219230

220-
instance PluginMethod TextDocumentDefinition where
231+
instance PluginMethod Request TextDocumentDefinition where
221232
pluginEnabled _ msgParams pluginDesc _ =
222233
pluginResponsible uri pluginDesc
223234
where
224235
uri = msgParams ^. J.textDocument . J.uri
225-
combineResponses _ _ _ _ (x :| _) = x
226236

227-
instance PluginMethod TextDocumentTypeDefinition where
237+
instance PluginMethod Request TextDocumentTypeDefinition where
228238
pluginEnabled _ msgParams pluginDesc _ =
229239
pluginResponsible uri pluginDesc
230240
where
231241
uri = msgParams ^. J.textDocument . J.uri
232-
combineResponses _ _ _ _ (x :| _) = x
233242

234-
instance PluginMethod TextDocumentDocumentHighlight where
243+
instance PluginMethod Request TextDocumentDocumentHighlight where
235244
pluginEnabled _ msgParams pluginDesc _ =
236245
pluginResponsible uri pluginDesc
237246
where
238247
uri = msgParams ^. J.textDocument . J.uri
239248

240-
instance PluginMethod TextDocumentReferences where
249+
instance PluginMethod Request TextDocumentReferences where
241250
pluginEnabled _ msgParams pluginDesc _ =
242251
pluginResponsible uri pluginDesc
243252
where
244253
uri = msgParams ^. J.textDocument . J.uri
245254

246-
instance PluginMethod WorkspaceSymbol where
255+
instance PluginMethod Request WorkspaceSymbol where
247256
pluginEnabled _ _ _ _ = True
248257

249-
instance PluginMethod TextDocumentCodeLens where
258+
instance PluginMethod Request TextDocumentCodeLens where
250259
pluginEnabled _ msgParams pluginDesc config =
251260
pluginResponsible uri pluginDesc
252261
&& pluginEnabledConfig plcCodeLensOn (pluginId pluginDesc) config
253262
where
254263
uri = msgParams ^. J.textDocument . J.uri
255264

256-
instance PluginMethod TextDocumentRename where
265+
instance PluginMethod Request TextDocumentRename where
257266
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
258267
&& pluginEnabledConfig plcRenameOn (pluginId pluginDesc) config
259268
where
260269
uri = msgParams ^. J.textDocument . J.uri
261-
instance PluginMethod TextDocumentHover where
270+
instance PluginMethod Request TextDocumentHover where
262271
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
263272
&& pluginEnabledConfig plcHoverOn (pluginId pluginDesc) config
264273
where
265274
uri = msgParams ^. J.textDocument . J.uri
275+
276+
instance PluginMethod Request TextDocumentDocumentSymbol where
277+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
278+
&& pluginEnabledConfig plcSymbolsOn (pluginId pluginDesc) config
279+
where
280+
uri = msgParams ^. J.textDocument . J.uri
281+
282+
instance PluginMethod Request TextDocumentCompletion where
283+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
284+
&& pluginEnabledConfig plcCompletionOn (pluginId pluginDesc) config
285+
where
286+
uri = msgParams ^. J.textDocument . J.uri
287+
288+
instance PluginMethod Request TextDocumentFormatting where
289+
pluginEnabled STextDocumentFormatting msgParams pluginDesc conf =
290+
pluginResponsible uri pluginDesc && PluginId (formattingProvider conf) == pid
291+
where
292+
uri = msgParams ^. J.textDocument . J.uri
293+
pid = pluginId pluginDesc
294+
295+
instance PluginMethod Request TextDocumentRangeFormatting where
296+
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
297+
&& PluginId (formattingProvider conf) == pid
298+
where
299+
uri = msgParams ^. J.textDocument . J.uri
300+
pid = pluginId pluginDesc
301+
302+
instance PluginMethod Request TextDocumentPrepareCallHierarchy where
303+
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
304+
&& pluginEnabledConfig plcCallHierarchyOn pid conf
305+
where
306+
uri = msgParams ^. J.textDocument . J.uri
307+
pid = pluginId pluginDesc
308+
309+
instance PluginMethod Request TextDocumentSelectionRange where
310+
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcSelectionRangeOn pid conf
311+
where
312+
pid = pluginId pluginDesc
313+
314+
instance PluginMethod Request CallHierarchyIncomingCalls where
315+
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
316+
where
317+
pid = pluginId pluginDesc
318+
319+
instance PluginMethod Request CallHierarchyOutgoingCalls where
320+
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
321+
where
322+
pid = pluginId pluginDesc
323+
324+
instance PluginMethod Request CustomMethod where
325+
pluginEnabled _ _ _ _ = True
326+
327+
---
328+
instance PluginRequestMethod TextDocumentDefinition where
329+
combineResponses _ _ _ _ (x :| _) = x
330+
331+
instance PluginRequestMethod TextDocumentTypeDefinition where
332+
combineResponses _ _ _ _ (x :| _) = x
333+
334+
instance PluginRequestMethod TextDocumentDocumentHighlight where
335+
336+
instance PluginRequestMethod TextDocumentReferences where
337+
338+
instance PluginRequestMethod WorkspaceSymbol where
339+
340+
instance PluginRequestMethod TextDocumentCodeLens where
341+
342+
instance PluginRequestMethod TextDocumentRename where
343+
344+
instance PluginRequestMethod TextDocumentHover where
266345
combineResponses _ _ _ _ (catMaybes . toList -> hs) = h
267346
where
268347
r = listToMaybe $ mapMaybe (^. range) hs
269348
h = case foldMap (^. contents) hs of
270349
HoverContentsMS (List []) -> Nothing
271350
hh -> Just $ Hover hh r
272351

273-
instance PluginMethod TextDocumentDocumentSymbol where
274-
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
275-
&& pluginEnabledConfig plcSymbolsOn (pluginId pluginDesc) config
276-
where
277-
uri = msgParams ^. J.textDocument . J.uri
352+
instance PluginRequestMethod TextDocumentDocumentSymbol where
278353
combineResponses _ _ (ClientCapabilities _ tdc _ _ _) params xs = res
279354
where
280355
uri' = params ^. textDocument . uri
@@ -295,11 +370,7 @@ instance PluginMethod TextDocumentDocumentSymbol where
295370
si = SymbolInformation name' (ds ^. kind) Nothing (ds ^. deprecated) loc parent
296371
in [si] <> children'
297372

298-
instance PluginMethod TextDocumentCompletion where
299-
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
300-
&& pluginEnabledConfig plcCompletionOn (pluginId pluginDesc) config
301-
where
302-
uri = msgParams ^. J.textDocument . J.uri
373+
instance PluginRequestMethod TextDocumentCompletion where
303374
combineResponses _ conf _ _ (toList -> xs) = snd $ consumeCompletionResponse limit $ combine xs
304375
where
305376
limit = maxCompletions conf
@@ -327,60 +398,36 @@ instance PluginMethod TextDocumentCompletion where
327398
consumeCompletionResponse n (InL (List xx)) =
328399
consumeCompletionResponse n (InR (CompletionList isCompleteResponse (List xx)))
329400

330-
instance PluginMethod TextDocumentFormatting where
331-
pluginEnabled STextDocumentFormatting msgParams pluginDesc conf =
332-
pluginResponsible uri pluginDesc && PluginId (formattingProvider conf) == pid
333-
where
334-
uri = msgParams ^. J.textDocument . J.uri
335-
pid = pluginId pluginDesc
401+
instance PluginRequestMethod TextDocumentFormatting where
336402
combineResponses _ _ _ _ x = sconcat x
337403

338-
339-
instance PluginMethod TextDocumentRangeFormatting where
340-
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
341-
&& PluginId (formattingProvider conf) == pid
342-
where
343-
uri = msgParams ^. J.textDocument . J.uri
344-
pid = pluginId pluginDesc
404+
instance PluginRequestMethod TextDocumentRangeFormatting where
345405
combineResponses _ _ _ _ (x :| _) = x
346406

347-
instance PluginMethod TextDocumentPrepareCallHierarchy where
348-
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
349-
&& pluginEnabledConfig plcCallHierarchyOn pid conf
350-
where
351-
uri = msgParams ^. J.textDocument . J.uri
352-
pid = pluginId pluginDesc
407+
instance PluginRequestMethod TextDocumentPrepareCallHierarchy where
353408

354-
instance PluginMethod TextDocumentSelectionRange where
355-
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcSelectionRangeOn pid conf
356-
where
357-
pid = pluginId pluginDesc
409+
instance PluginRequestMethod TextDocumentSelectionRange where
358410
combineResponses _ _ _ _ (x :| _) = x
359411

360-
instance PluginMethod CallHierarchyIncomingCalls where
361-
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
362-
where
363-
pid = pluginId pluginDesc
412+
instance PluginRequestMethod CallHierarchyIncomingCalls where
364413

365-
instance PluginMethod CallHierarchyOutgoingCalls where
366-
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
367-
where
368-
pid = pluginId pluginDesc
414+
instance PluginRequestMethod CallHierarchyOutgoingCalls where
369415

370-
instance PluginMethod CustomMethod where
371-
pluginEnabled _ _ _ _ = True
416+
instance PluginRequestMethod CustomMethod where
372417
combineResponses _ _ _ _ (x :| _) = x
373-
374418
-- ---------------------------------------------------------------------
375419

376-
class HasTracing (MessageParams m) => PluginNotificationMethod (m :: Method FromClient Notification) where
377-
pluginEnabled2 :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
420+
class PluginMethod Notification m => PluginNotificationMethod (m :: Method FromClient Notification) where
421+
422+
423+
instance PluginMethod Notification TextDocumentDidOpen where
424+
425+
instance PluginMethod Notification TextDocumentDidChange where
426+
427+
instance PluginMethod Notification TextDocumentDidSave where
428+
429+
instance PluginMethod Notification TextDocumentDidClose where
378430

379-
default pluginEnabled2 :: (HasTextDocument (MessageParams m) doc, HasUri doc Uri)
380-
=> SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
381-
pluginEnabled2 _ params desc conf = pluginResponsible uri desc && plcGlobalOn (configForPlugin conf (pluginId desc))
382-
where
383-
uri = params ^. J.textDocument . J.uri
384431

385432
instance PluginNotificationMethod TextDocumentDidOpen where
386433

@@ -390,22 +437,30 @@ instance PluginNotificationMethod TextDocumentDidSave where
390437

391438
instance PluginNotificationMethod TextDocumentDidClose where
392439

440+
instance PluginMethod Notification WorkspaceDidChangeWatchedFiles where
441+
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
442+
443+
instance PluginMethod Notification WorkspaceDidChangeWorkspaceFolders where
444+
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
445+
446+
instance PluginMethod Notification WorkspaceDidChangeConfiguration where
447+
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
448+
449+
instance PluginMethod Notification Initialized where
450+
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
451+
393452
instance PluginNotificationMethod WorkspaceDidChangeWatchedFiles where
394-
pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
395453

396454
instance PluginNotificationMethod WorkspaceDidChangeWorkspaceFolders where
397-
pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
398455

399456
instance PluginNotificationMethod WorkspaceDidChangeConfiguration where
400-
pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
401457

402458
instance PluginNotificationMethod Initialized where
403-
pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
404459

405460
-- ---------------------------------------------------------------------
406461

407462
-- | Methods which have a PluginMethod instance
408-
data IdeMethod (m :: Method FromClient Request) = PluginMethod m => IdeMethod (SMethod m)
463+
data IdeMethod (m :: Method FromClient Request) = PluginRequestMethod m => IdeMethod (SMethod m)
409464
instance GEq IdeMethod where
410465
geq (IdeMethod a) (IdeMethod b) = geq a b
411466
instance GCompare IdeMethod where
@@ -451,7 +506,7 @@ type PluginNotificationMethodHandler a m = a -> VFS -> PluginId -> MessageParams
451506

452507
-- | Make a handler for plugins with no extra data
453508
mkPluginHandler
454-
:: PluginMethod m
509+
:: PluginRequestMethod m
455510
=> SClientMethod m
456511
-> PluginMethodHandler ideState m
457512
-> PluginHandlers ideState

0 commit comments

Comments
 (0)