@@ -69,6 +69,7 @@ import Language.LSP.Types.Lens as J (HasChildren (children),
6969import Language.LSP.VFS
7070import OpenTelemetry.Eventlog
7171import Options.Applicative (ParserInfo )
72+ import System.FilePath
7273import System.IO.Unsafe
7374import Text.Regex.TDFA.Text ()
7475
@@ -108,7 +109,7 @@ instance Show (IdeCommand st) where show _ = "<ide command>"
108109
109110-- ---------------------------------------------------------------------
110111
111- data PluginDescriptor ideState =
112+ data PluginDescriptor ( ideState :: * ) =
112113 PluginDescriptor { pluginId :: ! PluginId
113114 , pluginRules :: ! (Rules () )
114115 , pluginCommands :: ! [PluginCommand ideState ]
@@ -117,6 +118,7 @@ data PluginDescriptor ideState =
117118 , pluginNotificationHandlers :: PluginNotificationHandlers ideState
118119 , pluginModifyDynflags :: DynFlagsModifications
119120 , pluginCli :: Maybe (ParserInfo (IdeCommand ideState ))
121+ , pluginFileType :: [T. Text ]
120122 }
121123
122124-- | An existential wrapper of 'Properties'
@@ -162,7 +164,7 @@ defaultConfigDescriptor = ConfigDescriptor True False (mkCustomConfig emptyPrope
162164class HasTracing (MessageParams m ) => PluginMethod m where
163165
164166 -- | 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
166168
167169 -- | How to combine responses from different plugins
168170 combineResponses
@@ -177,11 +179,13 @@ class HasTracing (MessageParams m) => PluginMethod m where
177179 combineResponses _method _config _caps _params = sconcat
178180
179181instance 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
181186 combineResponses _method _config (ClientCapabilities _ textDocCaps _ _ _) (CodeActionParams _ _ _ _ context) resps =
182187 fmap compat $ List $ filter wasRequested $ (\ (List x) -> x) $ sconcat resps
183188 where
184-
185189 compat :: (Command |? CodeAction ) -> (Command |? CodeAction )
186190 compat x@ (InL _) = x
187191 compat x@ (InR action)
@@ -205,12 +209,31 @@ instance PluginMethod TextDocumentCodeAction where
205209 , Just caKind <- ca ^. kind = any (\ k -> k `codeActionKindSubsumes` caKind) allowed
206210 | otherwise = False
207211
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+
208220instance 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+
210227instance 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
212232instance 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
214237 combineResponses _ _ _ _ (catMaybes . toList -> hs) = h
215238 where
216239 r = listToMaybe $ mapMaybe (^. range) hs
@@ -219,7 +242,10 @@ instance PluginMethod TextDocumentHover where
219242 hh -> Just $ Hover hh r
220243
221244instance 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
223249 combineResponses _ _ (ClientCapabilities _ tdc _ _ _) params xs = res
224250 where
225251 uri' = params ^. textDocument . uri
@@ -241,7 +267,10 @@ instance PluginMethod TextDocumentDocumentSymbol where
241267 in [si] <> children'
242268
243269instance 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
245274 combineResponses _ conf _ _ (toList -> xs) = snd $ consumeCompletionResponse limit $ combine xs
246275 where
247276 limit = maxCompletions conf
@@ -270,32 +299,82 @@ instance PluginMethod TextDocumentCompletion where
270299 consumeCompletionResponse n (InR (CompletionList isCompleteResponse (List xx)))
271300
272301instance 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+
275309
276310instance 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
278316 combineResponses _ _ _ _ (x :| _) = x
279317
280318instance 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
282324
283325instance PluginMethod TextDocumentSelectionRange where
284- pluginEnabled _ = pluginEnabledConfig plcSelectionRangeOn
326+ pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcSelectionRangeOn pid conf
327+ where
328+ pid = pluginId pluginDesc
285329 combineResponses _ _ _ _ (x :| _) = x
286330
287331instance PluginMethod CallHierarchyIncomingCalls where
288- pluginEnabled _ = pluginEnabledConfig plcCallHierarchyOn
332+ pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
333+ where
334+ pid = pluginId pluginDesc
289335
290336instance PluginMethod CallHierarchyOutgoingCalls where
291- pluginEnabled _ = pluginEnabledConfig plcCallHierarchyOn
337+ pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
338+ where
339+ pid = pluginId pluginDesc
292340
293341instance PluginMethod CustomMethod where
294- pluginEnabled _ _ _ = True
342+ pluginEnabled _ _ _ _ = True
295343 combineResponses _ _ _ _ (x :| _) = x
296344
297345-- ---------------------------------------------------------------------
298346
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+
299378-- | Methods which have a PluginMethod instance
300379data IdeMethod (m :: Method FromClient Request ) = PluginMethod m => IdeMethod (SMethod m )
301380instance GEq IdeMethod where
@@ -304,7 +383,7 @@ instance GCompare IdeMethod where
304383 gcompare (IdeMethod a) (IdeMethod b) = gcompare a b
305384
306385-- | 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 )
308387instance GEq IdeNotification where
309388 geq (IdeNotification a) (IdeNotification b) = geq a b
310389instance GCompare IdeNotification where
@@ -353,7 +432,7 @@ mkPluginHandler m f = PluginHandlers $ DMap.singleton (IdeMethod m) (PluginHandl
353432
354433-- | Make a handler for plugins with no extra data
355434mkPluginNotificationHandler
356- :: HasTracing ( MessageParams m )
435+ :: PluginNotificationMethod m
357436 => SClientMethod (m :: Method FromClient Notification )
358437 -> PluginNotificationMethodHandler ideState m
359438 -> PluginNotificationHandlers ideState
@@ -373,6 +452,20 @@ defaultPluginDescriptor plId =
373452 mempty
374453 mempty
375454 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" ]
376469
377470newtype CommandId = CommandId T. Text
378471 deriving (Show , Read , Eq , Ord )
0 commit comments