17
17
{-# LANGUAGE TypeFamilies #-}
18
18
{-# LANGUAGE UndecidableInstances #-}
19
19
{-# LANGUAGE ViewPatterns #-}
20
+ {-# LANGUAGE MultiParamTypeClasses #-}
20
21
21
22
module Ide.Types
22
23
where
@@ -161,11 +162,18 @@ defaultConfigDescriptor = ConfigDescriptor True False (mkCustomConfig emptyPrope
161
162
-- | Methods that can be handled by plugins.
162
163
-- 'ExtraParams' captures any extra data the IDE passes to the handlers for this method
163
164
-- 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
165
166
166
167
-- | Parse the configuration to check if this plugin is enabled
167
168
pluginEnabled :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
168
169
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
169
177
-- | How to combine responses from different plugins
170
178
combineResponses
171
179
:: SMethod m
@@ -178,11 +186,14 @@ class HasTracing (MessageParams m) => PluginMethod m where
178
186
=> SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m
179
187
combineResponses _method _config _caps _params = sconcat
180
188
181
- instance PluginMethod TextDocumentCodeAction where
189
+
190
+ instance PluginMethod Request TextDocumentCodeAction where
182
191
pluginEnabled _ msgParams pluginDesc config =
183
192
pluginResponsible uri pluginDesc && pluginEnabledConfig plcCodeActionsOn (pluginId pluginDesc) config
184
193
where
185
194
uri = msgParams ^. J. textDocument . J. uri
195
+
196
+ instance PluginRequestMethod TextDocumentCodeAction where
186
197
combineResponses _method _config (ClientCapabilities _ textDocCaps _ _ _) (CodeActionParams _ _ _ _ context) resps =
187
198
fmap compat $ List $ filter wasRequested $ (\ (List x) -> x) $ sconcat resps
188
199
where
@@ -217,64 +228,128 @@ pluginResponsible uri pluginDesc
217
228
where
218
229
mfp = uriToFilePath uri
219
230
220
- instance PluginMethod TextDocumentDefinition where
231
+ instance PluginMethod Request TextDocumentDefinition where
221
232
pluginEnabled _ msgParams pluginDesc _ =
222
233
pluginResponsible uri pluginDesc
223
234
where
224
235
uri = msgParams ^. J. textDocument . J. uri
225
- combineResponses _ _ _ _ (x :| _) = x
226
236
227
- instance PluginMethod TextDocumentTypeDefinition where
237
+ instance PluginMethod Request TextDocumentTypeDefinition where
228
238
pluginEnabled _ msgParams pluginDesc _ =
229
239
pluginResponsible uri pluginDesc
230
240
where
231
241
uri = msgParams ^. J. textDocument . J. uri
232
- combineResponses _ _ _ _ (x :| _) = x
233
242
234
- instance PluginMethod TextDocumentDocumentHighlight where
243
+ instance PluginMethod Request TextDocumentDocumentHighlight where
235
244
pluginEnabled _ msgParams pluginDesc _ =
236
245
pluginResponsible uri pluginDesc
237
246
where
238
247
uri = msgParams ^. J. textDocument . J. uri
239
248
240
- instance PluginMethod TextDocumentReferences where
249
+ instance PluginMethod Request TextDocumentReferences where
241
250
pluginEnabled _ msgParams pluginDesc _ =
242
251
pluginResponsible uri pluginDesc
243
252
where
244
253
uri = msgParams ^. J. textDocument . J. uri
245
254
246
- instance PluginMethod WorkspaceSymbol where
255
+ instance PluginMethod Request WorkspaceSymbol where
247
256
pluginEnabled _ _ _ _ = True
248
257
249
- instance PluginMethod TextDocumentCodeLens where
258
+ instance PluginMethod Request TextDocumentCodeLens where
250
259
pluginEnabled _ msgParams pluginDesc config =
251
260
pluginResponsible uri pluginDesc
252
261
&& pluginEnabledConfig plcCodeLensOn (pluginId pluginDesc) config
253
262
where
254
263
uri = msgParams ^. J. textDocument . J. uri
255
264
256
- instance PluginMethod TextDocumentRename where
265
+ instance PluginMethod Request TextDocumentRename where
257
266
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
258
267
&& pluginEnabledConfig plcRenameOn (pluginId pluginDesc) config
259
268
where
260
269
uri = msgParams ^. J. textDocument . J. uri
261
- instance PluginMethod TextDocumentHover where
270
+ instance PluginMethod Request TextDocumentHover where
262
271
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
263
272
&& pluginEnabledConfig plcHoverOn (pluginId pluginDesc) config
264
273
where
265
274
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
266
345
combineResponses _ _ _ _ (catMaybes . toList -> hs) = h
267
346
where
268
347
r = listToMaybe $ mapMaybe (^. range) hs
269
348
h = case foldMap (^. contents) hs of
270
349
HoverContentsMS (List [] ) -> Nothing
271
350
hh -> Just $ Hover hh r
272
351
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
278
353
combineResponses _ _ (ClientCapabilities _ tdc _ _ _) params xs = res
279
354
where
280
355
uri' = params ^. textDocument . uri
@@ -295,11 +370,7 @@ instance PluginMethod TextDocumentDocumentSymbol where
295
370
si = SymbolInformation name' (ds ^. kind) Nothing (ds ^. deprecated) loc parent
296
371
in [si] <> children'
297
372
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
303
374
combineResponses _ conf _ _ (toList -> xs) = snd $ consumeCompletionResponse limit $ combine xs
304
375
where
305
376
limit = maxCompletions conf
@@ -327,60 +398,36 @@ instance PluginMethod TextDocumentCompletion where
327
398
consumeCompletionResponse n (InL (List xx)) =
328
399
consumeCompletionResponse n (InR (CompletionList isCompleteResponse (List xx)))
329
400
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
336
402
combineResponses _ _ _ _ x = sconcat x
337
403
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
345
405
combineResponses _ _ _ _ (x :| _) = x
346
406
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
353
408
354
- instance PluginMethod TextDocumentSelectionRange where
355
- pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcSelectionRangeOn pid conf
356
- where
357
- pid = pluginId pluginDesc
409
+ instance PluginRequestMethod TextDocumentSelectionRange where
358
410
combineResponses _ _ _ _ (x :| _) = x
359
411
360
- instance PluginMethod CallHierarchyIncomingCalls where
361
- pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
362
- where
363
- pid = pluginId pluginDesc
412
+ instance PluginRequestMethod CallHierarchyIncomingCalls where
364
413
365
- instance PluginMethod CallHierarchyOutgoingCalls where
366
- pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
367
- where
368
- pid = pluginId pluginDesc
414
+ instance PluginRequestMethod CallHierarchyOutgoingCalls where
369
415
370
- instance PluginMethod CustomMethod where
371
- pluginEnabled _ _ _ _ = True
416
+ instance PluginRequestMethod CustomMethod where
372
417
combineResponses _ _ _ _ (x :| _) = x
373
-
374
418
-- ---------------------------------------------------------------------
375
419
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
378
430
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
384
431
385
432
instance PluginNotificationMethod TextDocumentDidOpen where
386
433
@@ -390,22 +437,30 @@ instance PluginNotificationMethod TextDocumentDidSave where
390
437
391
438
instance PluginNotificationMethod TextDocumentDidClose where
392
439
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
+
393
452
instance PluginNotificationMethod WorkspaceDidChangeWatchedFiles where
394
- pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
395
453
396
454
instance PluginNotificationMethod WorkspaceDidChangeWorkspaceFolders where
397
- pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
398
455
399
456
instance PluginNotificationMethod WorkspaceDidChangeConfiguration where
400
- pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
401
457
402
458
instance PluginNotificationMethod Initialized where
403
- pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
404
459
405
460
-- ---------------------------------------------------------------------
406
461
407
462
-- | 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 )
409
464
instance GEq IdeMethod where
410
465
geq (IdeMethod a) (IdeMethod b) = geq a b
411
466
instance GCompare IdeMethod where
@@ -451,7 +506,7 @@ type PluginNotificationMethodHandler a m = a -> VFS -> PluginId -> MessageParams
451
506
452
507
-- | Make a handler for plugins with no extra data
453
508
mkPluginHandler
454
- :: PluginMethod m
509
+ :: PluginRequestMethod m
455
510
=> SClientMethod m
456
511
-> PluginMethodHandler ideState m
457
512
-> PluginHandlers ideState
0 commit comments