@@ -58,8 +58,8 @@ asGhcIdePlugin :: Recorder (WithPriority Log) -> IdePlugins IdeState -> Plugin C
58
58
asGhcIdePlugin recorder (IdePlugins ls) =
59
59
mkPlugin rulesPlugins HLS. pluginRules <>
60
60
mkPlugin executeCommandPlugins HLS. pluginCommands <>
61
- mkPlugin extensiblePlugins HLS. pluginHandlers <>
62
- mkPlugin (extensibleNotificationPlugins recorder) HLS. pluginNotificationHandlers <>
61
+ mkPlugin ( extensiblePlugins recorder) id <>
62
+ mkPlugin (extensibleNotificationPlugins recorder) id <>
63
63
mkPlugin dynFlagsPlugins HLS. pluginModifyDynflags
64
64
where
65
65
@@ -153,55 +153,66 @@ executeCommandHandlers ecs = requestHandler SWorkspaceExecuteCommand execCmd
153
153
154
154
-- ---------------------------------------------------------------------
155
155
156
- extensiblePlugins :: [(PluginId , PluginHandlers IdeState )] -> Plugin Config
157
- extensiblePlugins xs = mempty { P. pluginHandlers = handlers }
156
+ extensiblePlugins :: Recorder ( WithPriority Log ) -> [(PluginId , PluginDescriptor IdeState )] -> Plugin Config
157
+ extensiblePlugins recorder xs = mempty { P. pluginHandlers = handlers }
158
158
where
159
159
IdeHandlers handlers' = foldMap bakePluginId xs
160
- bakePluginId :: (PluginId , PluginHandlers IdeState ) -> IdeHandlers
161
- bakePluginId (pid,PluginHandlers hs ) = IdeHandlers $ DMap. map
162
- (\ (PluginHandler f) -> IdeHandler [(pid,f pid)])
160
+ bakePluginId :: (PluginId , PluginDescriptor IdeState ) -> IdeHandlers
161
+ bakePluginId (pid,pluginDesc ) = IdeHandlers $ DMap. map
162
+ (\ (PluginHandler f) -> IdeHandler [(pid,pluginDesc, f pid)])
163
163
hs
164
+ where
165
+ PluginHandlers hs = HLS. pluginHandlers pluginDesc
164
166
handlers = mconcat $ do
165
167
(IdeMethod m :=> IdeHandler fs') <- DMap. assocs handlers'
166
168
pure $ requestHandler m $ \ ide params -> do
167
169
config <- Ide.PluginUtils. getClientConfig
168
- let fs = filter (\ (pid,_) -> pluginEnabled m pid config) fs'
170
+ -- Only run plugins that are allowed to run on this request
171
+ let fs = filter (\ (_, desc, _) -> pluginEnabled m params desc config) fs'
169
172
case nonEmpty fs of
170
- Nothing -> pure $ Left $ ResponseError InvalidRequest
171
- (" No plugin enabled for " <> T. pack (show m) <> " , available: " <> T. pack (show $ map fst fs))
172
- Nothing
173
+ Nothing -> do
174
+ logWith recorder Info LogNoEnabledPlugins
175
+ pure $ Left $ ResponseError InvalidRequest
176
+ ( " No plugin enabled for " <> T. pack (show m)
177
+ <> " , available: " <> T. pack (show $ map (\ (plid,_,_) -> plid) fs)
178
+ )
179
+ Nothing
173
180
Just fs -> do
174
181
let msg e pid = " Exception in plugin " <> T. pack (show pid) <> " while processing " <> T. pack (show m) <> " : " <> T. pack (show e)
175
- es <- runConcurrently msg (show m) fs ide params
182
+ handlers = fmap (\ (plid,_,handler) -> (plid,handler)) fs
183
+ es <- runConcurrently msg (show m) handlers ide params
176
184
let (errs,succs) = partitionEithers $ toList es
177
185
case nonEmpty succs of
178
186
Nothing -> pure $ Left $ combineErrors errs
179
187
Just xs -> do
180
188
caps <- LSP. getClientCapabilities
181
189
pure $ Right $ combineResponses m config caps params xs
190
+
182
191
-- ---------------------------------------------------------------------
183
192
184
- extensibleNotificationPlugins :: Recorder (WithPriority Log ) -> [(PluginId , PluginNotificationHandlers IdeState )] -> Plugin Config
193
+ extensibleNotificationPlugins :: Recorder (WithPriority Log ) -> [(PluginId , PluginDescriptor IdeState )] -> Plugin Config
185
194
extensibleNotificationPlugins recorder xs = mempty { P. pluginHandlers = handlers }
186
195
where
187
196
IdeNotificationHandlers handlers' = foldMap bakePluginId xs
188
- bakePluginId :: (PluginId , PluginNotificationHandlers IdeState ) -> IdeNotificationHandlers
189
- bakePluginId (pid,PluginNotificationHandlers hs ) = IdeNotificationHandlers $ DMap. map
190
- (\ (PluginNotificationHandler f) -> IdeNotificationHandler [(pid,f pid)])
197
+ bakePluginId :: (PluginId , PluginDescriptor IdeState ) -> IdeNotificationHandlers
198
+ bakePluginId (pid,pluginDesc ) = IdeNotificationHandlers $ DMap. map
199
+ (\ (PluginNotificationHandler f) -> IdeNotificationHandler [(pid,pluginDesc, f pid)])
191
200
hs
201
+ where PluginNotificationHandlers hs = HLS. pluginNotificationHandlers pluginDesc
192
202
handlers = mconcat $ do
193
203
(IdeNotification m :=> IdeNotificationHandler fs') <- DMap. assocs handlers'
194
204
pure $ notificationHandler m $ \ ide vfs params -> do
195
205
config <- Ide.PluginUtils. getClientConfig
196
- let fs = filter (\ (pid,_) -> plcGlobalOn $ configForPlugin config pid) fs'
206
+ -- Only run plugins that are allowed to run on this request
207
+ let fs = filter (\ (_, desc, _) -> pluginEnabled m params desc config) fs'
197
208
case nonEmpty fs of
198
209
Nothing -> do
199
- logWith recorder Info LogNoEnabledPlugins
200
- pure ()
210
+ logWith recorder Info LogNoEnabledPlugins
211
+ pure ()
201
212
Just fs -> do
202
213
-- We run the notifications in order, so the core ghcide provider
203
214
-- (which restarts the shake process) hopefully comes last
204
- mapM_ (\ (pid,f) -> otTracedProvider pid (fromString $ show m) $ f ide vfs params) fs
215
+ mapM_ (\ (pid,_ ,f) -> otTracedProvider pid (fromString $ show m) $ f ide vfs params) fs
205
216
206
217
-- ---------------------------------------------------------------------
207
218
@@ -210,6 +221,7 @@ runConcurrently
210
221
=> (SomeException -> PluginId -> T. Text )
211
222
-> String -- ^ label
212
223
-> NonEmpty (PluginId , a -> b -> m (NonEmpty (Either ResponseError d )))
224
+ -- ^ Enabled plugin actions that we are allowed to run
213
225
-> a
214
226
-> b
215
227
-> m (NonEmpty (Either ResponseError d ))
@@ -223,11 +235,11 @@ combineErrors xs = ResponseError InternalError (T.pack (show xs)) Nothing
223
235
224
236
-- | Combine the 'PluginHandler' for all plugins
225
237
newtype IdeHandler (m :: J. Method FromClient Request )
226
- = IdeHandler [(PluginId ,IdeState -> MessageParams m -> LSP. LspM Config (NonEmpty (Either ResponseError (ResponseResult m ))))]
238
+ = IdeHandler [(PluginId , PluginDescriptor IdeState , IdeState -> MessageParams m -> LSP. LspM Config (NonEmpty (Either ResponseError (ResponseResult m ))))]
227
239
228
240
-- | Combine the 'PluginHandler' for all plugins
229
241
newtype IdeNotificationHandler (m :: J. Method FromClient Notification )
230
- = IdeNotificationHandler [(PluginId , IdeState -> VFS -> MessageParams m -> LSP. LspM Config () )]
242
+ = IdeNotificationHandler [(PluginId , PluginDescriptor IdeState , IdeState -> VFS -> MessageParams m -> LSP. LspM Config () )]
231
243
-- type NotificationHandler (m :: Method FromClient Notification) = MessageParams m -> IO ()`
232
244
233
245
-- | Combine the 'PluginHandlers' for all plugins
0 commit comments