@@ -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,11 @@ data PluginDescriptor ideState =
117118 , pluginNotificationHandlers :: PluginNotificationHandlers ideState
118119 , pluginModifyDynflags :: DynFlagsModifications
119120 , pluginCli :: Maybe (ParserInfo (IdeCommand ideState ))
121+ , pluginFileType :: [T. Text ]
122+ -- ^ File extension of the files the plugin is responsible for.
123+ -- The plugin is only allowed to handle files with these extensions
124+ -- When writing handlers, etc. for this plugin it can be assumed that all handled files are of this type.
125+ -- The file extension must have a leading '.'.
120126 }
121127
122128-- | An existential wrapper of 'Properties'
@@ -162,7 +168,7 @@ defaultConfigDescriptor = ConfigDescriptor True False (mkCustomConfig emptyPrope
162168class HasTracing (MessageParams m ) => PluginMethod m where
163169
164170 -- | Parse the configuration to check if this plugin is enabled
165- pluginEnabled :: SMethod m -> PluginId -> Config -> Bool
171+ pluginEnabled :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
166172
167173 -- | How to combine responses from different plugins
168174 combineResponses
@@ -177,11 +183,13 @@ class HasTracing (MessageParams m) => PluginMethod m where
177183 combineResponses _method _config _caps _params = sconcat
178184
179185instance PluginMethod TextDocumentCodeAction where
180- pluginEnabled _ = pluginEnabledConfig plcCodeActionsOn
186+ pluginEnabled _ msgParams pluginDesc config =
187+ pluginResponsible uri pluginDesc && pluginEnabledConfig plcCodeActionsOn (pluginId pluginDesc) config
188+ where
189+ uri = msgParams ^. J. textDocument . J. uri
181190 combineResponses _method _config (ClientCapabilities _ textDocCaps _ _ _) (CodeActionParams _ _ _ _ context) resps =
182191 fmap compat $ List $ filter wasRequested $ (\ (List x) -> x) $ sconcat resps
183192 where
184-
185193 compat :: (Command |? CodeAction ) -> (Command |? CodeAction )
186194 compat x@ (InL _) = x
187195 compat x@ (InR action)
@@ -205,12 +213,34 @@ instance PluginMethod TextDocumentCodeAction where
205213 , Just caKind <- ca ^. kind = any (\ k -> k `codeActionKindSubsumes` caKind) allowed
206214 | otherwise = False
207215
216+ -- | Check whether the given plugin descriptor is responsible for the file with the given path.
217+ -- Compares the file extension of the file at the given path with the file extension
218+ -- the plugin is responsible for.
219+ pluginResponsible :: Uri -> PluginDescriptor c -> Bool
220+ pluginResponsible uri pluginDesc
221+ | Just fp <- mfp
222+ , T. pack (takeExtension fp) `elem` pluginFileType pluginDesc = True
223+ | otherwise = False
224+ where
225+ mfp = uriToFilePath uri
226+
208227instance PluginMethod TextDocumentCodeLens where
209- pluginEnabled _ = pluginEnabledConfig plcCodeLensOn
228+ pluginEnabled _ msgParams pluginDesc config =
229+ pluginResponsible uri pluginDesc
230+ && pluginEnabledConfig plcCodeLensOn (pluginId pluginDesc) config
231+ where
232+ uri = msgParams ^. J. textDocument . J. uri
233+
210234instance PluginMethod TextDocumentRename where
211- pluginEnabled _ = pluginEnabledConfig plcRenameOn
235+ pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
236+ && pluginEnabledConfig plcRenameOn (pluginId pluginDesc) config
237+ where
238+ uri = msgParams ^. J. textDocument . J. uri
212239instance PluginMethod TextDocumentHover where
213- pluginEnabled _ = pluginEnabledConfig plcHoverOn
240+ pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
241+ && pluginEnabledConfig plcHoverOn (pluginId pluginDesc) config
242+ where
243+ uri = msgParams ^. J. textDocument . J. uri
214244 combineResponses _ _ _ _ (catMaybes . toList -> hs) = h
215245 where
216246 r = listToMaybe $ mapMaybe (^. range) hs
@@ -219,7 +249,10 @@ instance PluginMethod TextDocumentHover where
219249 hh -> Just $ Hover hh r
220250
221251instance PluginMethod TextDocumentDocumentSymbol where
222- pluginEnabled _ = pluginEnabledConfig plcSymbolsOn
252+ pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
253+ && pluginEnabledConfig plcSymbolsOn (pluginId pluginDesc) config
254+ where
255+ uri = msgParams ^. J. textDocument . J. uri
223256 combineResponses _ _ (ClientCapabilities _ tdc _ _ _) params xs = res
224257 where
225258 uri' = params ^. textDocument . uri
@@ -241,7 +274,10 @@ instance PluginMethod TextDocumentDocumentSymbol where
241274 in [si] <> children'
242275
243276instance PluginMethod TextDocumentCompletion where
244- pluginEnabled _ = pluginEnabledConfig plcCompletionOn
277+ pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
278+ && pluginEnabledConfig plcCompletionOn (pluginId pluginDesc) config
279+ where
280+ uri = msgParams ^. J. textDocument . J. uri
245281 combineResponses _ conf _ _ (toList -> xs) = snd $ consumeCompletionResponse limit $ combine xs
246282 where
247283 limit = maxCompletions conf
@@ -270,32 +306,82 @@ instance PluginMethod TextDocumentCompletion where
270306 consumeCompletionResponse n (InR (CompletionList isCompleteResponse (List xx)))
271307
272308instance PluginMethod TextDocumentFormatting where
273- pluginEnabled _ pid conf = (PluginId $ formattingProvider conf) == pid
274- combineResponses _ _ _ _ (x :| _) = x
309+ pluginEnabled STextDocumentFormatting msgParams pluginDesc conf =
310+ pluginResponsible uri pluginDesc && PluginId (formattingProvider conf) == pid
311+ where
312+ uri = msgParams ^. J. textDocument . J. uri
313+ pid = pluginId pluginDesc
314+ combineResponses _ _ _ _ x = sconcat x
315+
275316
276317instance PluginMethod TextDocumentRangeFormatting where
277- pluginEnabled _ pid conf = (PluginId $ formattingProvider conf) == pid
318+ pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
319+ && PluginId (formattingProvider conf) == pid
320+ where
321+ uri = msgParams ^. J. textDocument . J. uri
322+ pid = pluginId pluginDesc
278323 combineResponses _ _ _ _ (x :| _) = x
279324
280325instance PluginMethod TextDocumentPrepareCallHierarchy where
281- pluginEnabled _ = pluginEnabledConfig plcCallHierarchyOn
326+ pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
327+ && pluginEnabledConfig plcCallHierarchyOn pid conf
328+ where
329+ uri = msgParams ^. J. textDocument . J. uri
330+ pid = pluginId pluginDesc
282331
283332instance PluginMethod TextDocumentSelectionRange where
284- pluginEnabled _ = pluginEnabledConfig plcSelectionRangeOn
333+ pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcSelectionRangeOn pid conf
334+ where
335+ pid = pluginId pluginDesc
285336 combineResponses _ _ _ _ (x :| _) = x
286337
287338instance PluginMethod CallHierarchyIncomingCalls where
288- pluginEnabled _ = pluginEnabledConfig plcCallHierarchyOn
339+ pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
340+ where
341+ pid = pluginId pluginDesc
289342
290343instance PluginMethod CallHierarchyOutgoingCalls where
291- pluginEnabled _ = pluginEnabledConfig plcCallHierarchyOn
344+ pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
345+ where
346+ pid = pluginId pluginDesc
292347
293348instance PluginMethod CustomMethod where
294- pluginEnabled _ _ _ = True
349+ pluginEnabled _ _ _ _ = True
295350 combineResponses _ _ _ _ (x :| _) = x
296351
297352-- ---------------------------------------------------------------------
298353
354+ class HasTracing (MessageParams m ) => PluginNotificationMethod (m :: Method FromClient Notification ) where
355+ pluginEnabled2 :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
356+
357+ default pluginEnabled2 :: (HasTextDocument (MessageParams m ) doc , HasUri doc Uri )
358+ => SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
359+ pluginEnabled2 _ params desc conf = pluginResponsible uri desc && plcGlobalOn (configForPlugin conf (pluginId desc))
360+ where
361+ uri = params ^. J. textDocument . J. uri
362+
363+ instance PluginNotificationMethod TextDocumentDidOpen where
364+
365+ instance PluginNotificationMethod TextDocumentDidChange where
366+
367+ instance PluginNotificationMethod TextDocumentDidSave where
368+
369+ instance PluginNotificationMethod TextDocumentDidClose where
370+
371+ instance PluginNotificationMethod WorkspaceDidChangeWatchedFiles where
372+ pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
373+
374+ instance PluginNotificationMethod WorkspaceDidChangeWorkspaceFolders where
375+ pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
376+
377+ instance PluginNotificationMethod WorkspaceDidChangeConfiguration where
378+ pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
379+
380+ instance PluginNotificationMethod Initialized where
381+ pluginEnabled2 _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)
382+
383+ -- ---------------------------------------------------------------------
384+
299385-- | Methods which have a PluginMethod instance
300386data IdeMethod (m :: Method FromClient Request ) = PluginMethod m => IdeMethod (SMethod m )
301387instance GEq IdeMethod where
@@ -304,7 +390,7 @@ instance GCompare IdeMethod where
304390 gcompare (IdeMethod a) (IdeMethod b) = gcompare a b
305391
306392-- | Methods which have a PluginMethod instance
307- data IdeNotification (m :: Method FromClient Notification ) = HasTracing ( MessageParams m ) => IdeNotification (SMethod m )
393+ data IdeNotification (m :: Method FromClient Notification ) = PluginNotificationMethod m => IdeNotification (SMethod m )
308394instance GEq IdeNotification where
309395 geq (IdeNotification a) (IdeNotification b) = geq a b
310396instance GCompare IdeNotification where
@@ -353,7 +439,7 @@ mkPluginHandler m f = PluginHandlers $ DMap.singleton (IdeMethod m) (PluginHandl
353439
354440-- | Make a handler for plugins with no extra data
355441mkPluginNotificationHandler
356- :: HasTracing ( MessageParams m )
442+ :: PluginNotificationMethod m
357443 => SClientMethod (m :: Method FromClient Notification )
358444 -> PluginNotificationMethodHandler ideState m
359445 -> PluginNotificationHandlers ideState
@@ -373,6 +459,20 @@ defaultPluginDescriptor plId =
373459 mempty
374460 mempty
375461 Nothing
462+ [" .hs" , " .lhs" , " .hs-boot" ]
463+
464+ defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState
465+ defaultCabalPluginDescriptor plId =
466+ PluginDescriptor
467+ plId
468+ mempty
469+ mempty
470+ mempty
471+ defaultConfigDescriptor
472+ mempty
473+ mempty
474+ Nothing
475+ [" .cabal" ]
376476
377477newtype CommandId = CommandId T. Text
378478 deriving (Show , Read , Eq , Ord )
0 commit comments