@@ -69,6 +69,7 @@ import Language.LSP.Types.Lens as J (HasChildren (children),
69
69
import Language.LSP.VFS
70
70
import OpenTelemetry.Eventlog
71
71
import Options.Applicative (ParserInfo )
72
+ import System.FilePath
72
73
import System.IO.Unsafe
73
74
import Text.Regex.TDFA.Text ()
74
75
@@ -108,7 +109,7 @@ instance Show (IdeCommand st) where show _ = "<ide command>"
108
109
109
110
-- ---------------------------------------------------------------------
110
111
111
- data PluginDescriptor ideState =
112
+ data PluginDescriptor ( ideState :: * ) =
112
113
PluginDescriptor { pluginId :: ! PluginId
113
114
, pluginRules :: ! (Rules () )
114
115
, pluginCommands :: ! [PluginCommand ideState ]
@@ -117,6 +118,7 @@ data PluginDescriptor ideState =
117
118
, pluginNotificationHandlers :: PluginNotificationHandlers ideState
118
119
, pluginModifyDynflags :: DynFlagsModifications
119
120
, pluginCli :: Maybe (ParserInfo (IdeCommand ideState ))
121
+ , pluginFileType :: [T. Text ]
120
122
}
121
123
122
124
-- | An existential wrapper of 'Properties'
@@ -162,7 +164,7 @@ defaultConfigDescriptor = ConfigDescriptor True False (mkCustomConfig emptyPrope
162
164
class HasTracing (MessageParams m ) => PluginMethod m where
163
165
164
166
-- | Parse the configuration to check if this plugin is enabled
165
- pluginEnabled :: SMethod m -> PluginId -> Config -> Bool
167
+ pluginEnabled :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
166
168
167
169
-- | How to combine responses from different plugins
168
170
combineResponses
@@ -177,11 +179,13 @@ class HasTracing (MessageParams m) => PluginMethod m where
177
179
combineResponses _method _config _caps _params = sconcat
178
180
179
181
instance PluginMethod TextDocumentCodeAction where
180
- pluginEnabled _ = pluginEnabledConfig plcCodeActionsOn
182
+ pluginEnabled _ msgParams pluginDesc config =
183
+ pluginResponsible uri pluginDesc && pluginEnabledConfig plcCodeActionsOn (pluginId pluginDesc) config
184
+ where
185
+ uri = msgParams ^. J. textDocument . J. uri
181
186
combineResponses _method _config (ClientCapabilities _ textDocCaps _ _ _) (CodeActionParams _ _ _ _ context) resps =
182
187
fmap compat $ List $ filter wasRequested $ (\ (List x) -> x) $ sconcat resps
183
188
where
184
-
185
189
compat :: (Command |? CodeAction ) -> (Command |? CodeAction )
186
190
compat x@ (InL _) = x
187
191
compat x@ (InR action)
@@ -205,12 +209,31 @@ instance PluginMethod TextDocumentCodeAction where
205
209
, Just caKind <- ca ^. kind = any (\ k -> k `codeActionKindSubsumes` caKind) allowed
206
210
| otherwise = False
207
211
212
+ pluginResponsible :: Uri -> PluginDescriptor c -> Bool
213
+ pluginResponsible uri pluginDesc
214
+ | Just fp <- mfp
215
+ , T. pack (takeExtension fp) `elem` pluginFileType pluginDesc = True
216
+ | otherwise = False
217
+ where
218
+ mfp = uriToFilePath uri
219
+
208
220
instance PluginMethod TextDocumentCodeLens where
209
- pluginEnabled _ = pluginEnabledConfig plcCodeLensOn
221
+ pluginEnabled _ msgParams pluginDesc config =
222
+ pluginResponsible uri pluginDesc
223
+ && pluginEnabledConfig plcCodeLensOn (pluginId pluginDesc) config
224
+ where
225
+ uri = msgParams ^. J. textDocument . J. uri
226
+
210
227
instance PluginMethod TextDocumentRename where
211
- pluginEnabled _ = pluginEnabledConfig plcRenameOn
228
+ pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
229
+ && pluginEnabledConfig plcRenameOn (pluginId pluginDesc) config
230
+ where
231
+ uri = msgParams ^. J. textDocument . J. uri
212
232
instance PluginMethod TextDocumentHover where
213
- pluginEnabled _ = pluginEnabledConfig plcHoverOn
233
+ pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
234
+ && pluginEnabledConfig plcHoverOn (pluginId pluginDesc) config
235
+ where
236
+ uri = msgParams ^. J. textDocument . J. uri
214
237
combineResponses _ _ _ _ (catMaybes . toList -> hs) = h
215
238
where
216
239
r = listToMaybe $ mapMaybe (^. range) hs
@@ -219,7 +242,10 @@ instance PluginMethod TextDocumentHover where
219
242
hh -> Just $ Hover hh r
220
243
221
244
instance PluginMethod TextDocumentDocumentSymbol where
222
- pluginEnabled _ = pluginEnabledConfig plcSymbolsOn
245
+ pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
246
+ && pluginEnabledConfig plcSymbolsOn (pluginId pluginDesc) config
247
+ where
248
+ uri = msgParams ^. J. textDocument . J. uri
223
249
combineResponses _ _ (ClientCapabilities _ tdc _ _ _) params xs = res
224
250
where
225
251
uri' = params ^. textDocument . uri
@@ -241,7 +267,10 @@ instance PluginMethod TextDocumentDocumentSymbol where
241
267
in [si] <> children'
242
268
243
269
instance PluginMethod TextDocumentCompletion where
244
- pluginEnabled _ = pluginEnabledConfig plcCompletionOn
270
+ pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
271
+ && pluginEnabledConfig plcCompletionOn (pluginId pluginDesc) config
272
+ where
273
+ uri = msgParams ^. J. textDocument . J. uri
245
274
combineResponses _ conf _ _ (toList -> xs) = snd $ consumeCompletionResponse limit $ combine xs
246
275
where
247
276
limit = maxCompletions conf
@@ -270,32 +299,82 @@ instance PluginMethod TextDocumentCompletion where
270
299
consumeCompletionResponse n (InR (CompletionList isCompleteResponse (List xx)))
271
300
272
301
instance PluginMethod TextDocumentFormatting where
273
- pluginEnabled _ pid conf = (PluginId $ formattingProvider conf) == pid
274
- combineResponses _ _ _ _ (x :| _) = x
302
+ pluginEnabled STextDocumentFormatting msgParams pluginDesc conf =
303
+ pluginResponsible uri pluginDesc && PluginId (formattingProvider conf) == pid
304
+ where
305
+ uri = msgParams ^. J. textDocument . J. uri
306
+ pid = pluginId pluginDesc
307
+ combineResponses _ _ _ _ x = sconcat x
308
+
275
309
276
310
instance PluginMethod TextDocumentRangeFormatting where
277
- pluginEnabled _ pid conf = (PluginId $ formattingProvider conf) == pid
311
+ pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
312
+ && PluginId (formattingProvider conf) == pid
313
+ where
314
+ uri = msgParams ^. J. textDocument . J. uri
315
+ pid = pluginId pluginDesc
278
316
combineResponses _ _ _ _ (x :| _) = x
279
317
280
318
instance PluginMethod TextDocumentPrepareCallHierarchy where
281
- pluginEnabled _ = pluginEnabledConfig plcCallHierarchyOn
319
+ pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
320
+ && pluginEnabledConfig plcCallHierarchyOn pid conf
321
+ where
322
+ uri = msgParams ^. J. textDocument . J. uri
323
+ pid = pluginId pluginDesc
282
324
283
325
instance PluginMethod TextDocumentSelectionRange where
284
- pluginEnabled _ = pluginEnabledConfig plcSelectionRangeOn
326
+ pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcSelectionRangeOn pid conf
327
+ where
328
+ pid = pluginId pluginDesc
285
329
combineResponses _ _ _ _ (x :| _) = x
286
330
287
331
instance PluginMethod CallHierarchyIncomingCalls where
288
- pluginEnabled _ = pluginEnabledConfig plcCallHierarchyOn
332
+ pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
333
+ where
334
+ pid = pluginId pluginDesc
289
335
290
336
instance PluginMethod CallHierarchyOutgoingCalls where
291
- pluginEnabled _ = pluginEnabledConfig plcCallHierarchyOn
337
+ pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
338
+ where
339
+ pid = pluginId pluginDesc
292
340
293
341
instance PluginMethod CustomMethod where
294
- pluginEnabled _ _ _ = True
342
+ pluginEnabled _ _ _ _ = True
295
343
combineResponses _ _ _ _ (x :| _) = x
296
344
297
345
-- ---------------------------------------------------------------------
298
346
347
+ class HasTracing (MessageParams m ) => PluginNotificationMethod (m :: Method FromClient Notification ) where
348
+ pluginEnabled2 :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
349
+
350
+ default pluginEnabled2 :: (HasTextDocument (MessageParams m ) doc , HasUri doc Uri )
351
+ => SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
352
+ pluginEnabled2 _ params desc conf = pluginResponsible uri desc && plcGlobalOn (configForPlugin conf (pluginId desc))
353
+ where
354
+ uri = params ^. J. textDocument . J. uri
355
+
356
+ instance PluginNotificationMethod TextDocumentDidOpen where
357
+
358
+ instance PluginNotificationMethod TextDocumentDidChange where
359
+
360
+ instance PluginNotificationMethod TextDocumentDidSave where
361
+
362
+ instance PluginNotificationMethod TextDocumentDidClose where
363
+
364
+ instance PluginNotificationMethod WorkspaceDidChangeWatchedFiles where
365
+ pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
366
+
367
+ instance PluginNotificationMethod WorkspaceDidChangeWorkspaceFolders where
368
+ pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
369
+
370
+ instance PluginNotificationMethod WorkspaceDidChangeConfiguration where
371
+ pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
372
+
373
+ instance PluginNotificationMethod Initialized where
374
+ pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
375
+
376
+ -- ---------------------------------------------------------------------
377
+
299
378
-- | Methods which have a PluginMethod instance
300
379
data IdeMethod (m :: Method FromClient Request ) = PluginMethod m => IdeMethod (SMethod m )
301
380
instance GEq IdeMethod where
@@ -304,7 +383,7 @@ instance GCompare IdeMethod where
304
383
gcompare (IdeMethod a) (IdeMethod b) = gcompare a b
305
384
306
385
-- | Methods which have a PluginMethod instance
307
- data IdeNotification (m :: Method FromClient Notification ) = HasTracing ( MessageParams m ) => IdeNotification (SMethod m )
386
+ data IdeNotification (m :: Method FromClient Notification ) = PluginNotificationMethod m => IdeNotification (SMethod m )
308
387
instance GEq IdeNotification where
309
388
geq (IdeNotification a) (IdeNotification b) = geq a b
310
389
instance GCompare IdeNotification where
@@ -353,7 +432,7 @@ mkPluginHandler m f = PluginHandlers $ DMap.singleton (IdeMethod m) (PluginHandl
353
432
354
433
-- | Make a handler for plugins with no extra data
355
434
mkPluginNotificationHandler
356
- :: HasTracing ( MessageParams m )
435
+ :: PluginNotificationMethod m
357
436
=> SClientMethod (m :: Method FromClient Notification )
358
437
-> PluginNotificationMethodHandler ideState m
359
438
-> PluginNotificationHandlers ideState
@@ -373,6 +452,20 @@ defaultPluginDescriptor plId =
373
452
mempty
374
453
mempty
375
454
Nothing
455
+ [" .hs" , " .lhs" ]
456
+
457
+ defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState
458
+ defaultCabalPluginDescriptor plId =
459
+ PluginDescriptor
460
+ plId
461
+ mempty
462
+ mempty
463
+ mempty
464
+ defaultConfigDescriptor
465
+ mempty
466
+ mempty
467
+ Nothing
468
+ [" .cabal" ]
376
469
377
470
newtype CommandId = CommandId T. Text
378
471
deriving (Show , Read , Eq , Ord )
0 commit comments