Skip to content

Commit eebf169

Browse files
committed
Generalise file extension handling for plugins
1 parent 630a123 commit eebf169

File tree

3 files changed

+70
-19
lines changed

3 files changed

+70
-19
lines changed

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

Lines changed: 9 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,7 @@ import Text.Regex.TDFA.Text ()
3939
import UnliftIO (MonadUnliftIO)
4040
import UnliftIO.Async (forConcurrently)
4141
import UnliftIO.Exception (catchAny)
42+
import Data.Maybe
4243

4344
-- ---------------------------------------------------------------------
4445
--
@@ -48,7 +49,7 @@ asGhcIdePlugin :: IdePlugins IdeState -> Plugin Config
4849
asGhcIdePlugin (IdePlugins ls) =
4950
mkPlugin rulesPlugins HLS.pluginRules <>
5051
mkPlugin executeCommandPlugins HLS.pluginCommands <>
51-
mkPlugin extensiblePlugins HLS.pluginHandlers <>
52+
mkPlugin extensiblePlugins id <>
5253
mkPlugin extensibleNotificationPlugins HLS.pluginNotificationHandlers <>
5354
mkPlugin dynFlagsPlugins HLS.pluginModifyDynflags
5455
where
@@ -143,19 +144,22 @@ executeCommandHandlers ecs = requestHandler SWorkspaceExecuteCommand execCmd
143144

144145
-- ---------------------------------------------------------------------
145146

146-
extensiblePlugins :: [(PluginId, PluginHandlers IdeState)] -> Plugin Config
147+
extensiblePlugins :: [(PluginId, PluginDescriptor IdeState)] -> Plugin Config
147148
extensiblePlugins xs = mempty { P.pluginHandlers = handlers }
148149
where
150+
getPluginDescriptor pid = fromJust $ lookup pid xs
149151
IdeHandlers handlers' = foldMap bakePluginId xs
150-
bakePluginId :: (PluginId, PluginHandlers IdeState) -> IdeHandlers
151-
bakePluginId (pid,PluginHandlers hs) = IdeHandlers $ DMap.map
152+
bakePluginId :: (PluginId, PluginDescriptor IdeState) -> IdeHandlers
153+
bakePluginId (pid,pluginDesc) = IdeHandlers $ DMap.map
152154
(\(PluginHandler f) -> IdeHandler [(pid,f pid)])
153155
hs
156+
where
157+
PluginHandlers hs = HLS.pluginHandlers pluginDesc
154158
handlers = mconcat $ do
155159
(IdeMethod m :=> IdeHandler fs') <- DMap.assocs handlers'
156160
pure $ requestHandler m $ \ide params -> do
157161
config <- Ide.PluginUtils.getClientConfig
158-
let fs = filter (\(pid,_) -> pluginEnabled m pid config) fs'
162+
let fs = filter (\(pid,_) -> pluginEnabled m params (getPluginDescriptor pid) config) fs'
159163
case nonEmpty fs of
160164
Nothing -> pure $ Left $ ResponseError InvalidRequest
161165
("No plugin enabled for " <> T.pack (show m) <> ", available: " <> T.pack (show $ map fst fs))

hls-plugin-api/hls-plugin-api.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,7 @@ library
4343
, dependent-sum
4444
, Diff ^>=0.4.0
4545
, dlist
46+
, filepath
4647
, ghc
4748
, ghc-api-compat
4849
, hashable

hls-plugin-api/src/Ide/Types.hs

Lines changed: 60 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,7 @@ import OpenTelemetry.Eventlog
6666
import Options.Applicative (ParserInfo)
6767
import System.IO.Unsafe
6868
import Text.Regex.TDFA.Text ()
69+
import System.FilePath
6970

7071
-- ---------------------------------------------------------------------
7172

@@ -158,7 +159,7 @@ defaultConfigDescriptor = ConfigDescriptor True False (mkCustomConfig emptyPrope
158159
class HasTracing (MessageParams m) => PluginMethod m where
159160

160161
-- | Parse the configuration to check if this plugin is enabled
161-
pluginEnabled :: SMethod m -> PluginId -> Config -> Bool
162+
pluginEnabled :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
162163

163164
-- | How to combine responses from different plugins
164165
combineResponses
@@ -173,11 +174,14 @@ class HasTracing (MessageParams m) => PluginMethod m where
173174
combineResponses _method _config _caps _params = sconcat
174175

175176
instance PluginMethod TextDocumentCodeAction where
176-
pluginEnabled _ = pluginEnabledConfig plcCodeActionsOn
177+
pluginEnabled _ msgParams pluginDesc
178+
| pluginResponsible uri pluginDesc = pluginEnabledConfig plcCodeActionsOn (pluginId pluginDesc)
179+
| otherwise = const False
180+
where
181+
uri = msgParams ^. J.textDocument . J.uri
177182
combineResponses _method _config (ClientCapabilities _ textDocCaps _ _) (CodeActionParams _ _ _ _ context) resps =
178183
fmap compat $ List $ filter wasRequested $ (\(List x) -> x) $ sconcat resps
179184
where
180-
181185
compat :: (Command |? CodeAction) -> (Command |? CodeAction)
182186
compat x@(InL _) = x
183187
compat x@(InR action)
@@ -196,12 +200,31 @@ instance PluginMethod TextDocumentCodeAction where
196200
, Just caKind <- ca ^. kind = caKind `elem` allowed
197201
| otherwise = False
198202

203+
pluginResponsible :: Uri -> PluginDescriptor c -> Bool
204+
pluginResponsible uri pluginDesc
205+
| Just fp <- mfp
206+
, T.pack (takeExtension fp) `elem` pluginFileType pluginDesc = True
207+
| otherwise = False
208+
where
209+
mfp = uriToFilePath uri
210+
199211
instance PluginMethod TextDocumentCodeLens where
200-
pluginEnabled _ = pluginEnabledConfig plcCodeLensOn
212+
pluginEnabled _ msgParams pluginDesc config =
213+
pluginResponsible uri pluginDesc
214+
&& pluginEnabledConfig plcCodeLensOn (pluginId pluginDesc) config
215+
where
216+
uri = msgParams ^. J.textDocument . J.uri
217+
201218
instance PluginMethod TextDocumentRename where
202-
pluginEnabled _ = pluginEnabledConfig plcRenameOn
219+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
220+
&& pluginEnabledConfig plcRenameOn (pluginId pluginDesc) config
221+
where
222+
uri = msgParams ^. J.textDocument . J.uri
203223
instance PluginMethod TextDocumentHover where
204-
pluginEnabled _ = pluginEnabledConfig plcHoverOn
224+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
225+
&& pluginEnabledConfig plcHoverOn (pluginId pluginDesc) config
226+
where
227+
uri = msgParams ^. J.textDocument . J.uri
205228
combineResponses _ _ _ _ (catMaybes . toList -> hs) = h
206229
where
207230
r = listToMaybe $ mapMaybe (^. range) hs
@@ -210,7 +233,10 @@ instance PluginMethod TextDocumentHover where
210233
hh -> Just $ Hover hh r
211234

212235
instance PluginMethod TextDocumentDocumentSymbol where
213-
pluginEnabled _ = pluginEnabledConfig plcSymbolsOn
236+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
237+
&& pluginEnabledConfig plcSymbolsOn (pluginId pluginDesc) config
238+
where
239+
uri = msgParams ^. J.textDocument . J.uri
214240
combineResponses _ _ (ClientCapabilities _ tdc _ _) params xs = res
215241
where
216242
uri' = params ^. textDocument . uri
@@ -232,7 +258,10 @@ instance PluginMethod TextDocumentDocumentSymbol where
232258
in [si] <> children'
233259

234260
instance PluginMethod TextDocumentCompletion where
235-
pluginEnabled _ = pluginEnabledConfig plcCompletionOn
261+
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
262+
&& pluginEnabledConfig plcCompletionOn (pluginId pluginDesc) config
263+
where
264+
uri = msgParams ^. J.textDocument . J.uri
236265
combineResponses _ conf _ _ (toList -> xs) = snd $ consumeCompletionResponse limit $ combine xs
237266
where
238267
limit = maxCompletions conf
@@ -261,22 +290,39 @@ instance PluginMethod TextDocumentCompletion where
261290
consumeCompletionResponse n (InR (CompletionList isCompleteResponse (List xx)))
262291

263292
instance PluginMethod TextDocumentFormatting where
264-
pluginEnabled STextDocumentFormatting pid conf =
265-
PluginId (formattingProvider conf) == pid || PluginId (cabalFormattingProvider conf) == pid
293+
pluginEnabled STextDocumentFormatting msgParams pluginDesc conf =
294+
pluginResponsible uri pluginDesc
295+
&& (PluginId (formattingProvider conf) == pid || PluginId (cabalFormattingProvider conf) == pid)
296+
where
297+
uri = msgParams ^. J.textDocument . J.uri
298+
pid = pluginId pluginDesc
266299
combineResponses _ _ _ _ x = sconcat x
267300

301+
268302
instance PluginMethod TextDocumentRangeFormatting where
269-
pluginEnabled _ pid conf = PluginId (formattingProvider conf) == pid
303+
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
304+
&& PluginId (formattingProvider conf) == pid
305+
where
306+
uri = msgParams ^. J.textDocument . J.uri
307+
pid = pluginId pluginDesc
270308
combineResponses _ _ _ _ (x :| _) = x
271309

272310
instance PluginMethod TextDocumentPrepareCallHierarchy where
273-
pluginEnabled _ = pluginEnabledConfig plcCallHierarchyOn
311+
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
312+
&& pluginEnabledConfig plcCallHierarchyOn pid conf
313+
where
314+
uri = msgParams ^. J.textDocument . J.uri
315+
pid = pluginId pluginDesc
274316

275317
instance PluginMethod CallHierarchyIncomingCalls where
276-
pluginEnabled _ = pluginEnabledConfig plcCallHierarchyOn
318+
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
319+
where
320+
pid = pluginId pluginDesc
277321

278322
instance PluginMethod CallHierarchyOutgoingCalls where
279-
pluginEnabled _ = pluginEnabledConfig plcCallHierarchyOn
323+
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
324+
where
325+
pid = pluginId pluginDesc
280326

281327
-- ---------------------------------------------------------------------
282328

0 commit comments

Comments
 (0)