@@ -58,7 +58,7 @@ asGhcIdePlugin :: Recorder (WithPriority Log) -> IdePlugins IdeState -> Plugin C
5858asGhcIdePlugin recorder (IdePlugins ls) =
5959 mkPlugin rulesPlugins HLS. pluginRules <>
6060 mkPlugin executeCommandPlugins HLS. pluginCommands <>
61- mkPlugin extensiblePlugins id <>
61+ mkPlugin ( extensiblePlugins recorder) id <>
6262 mkPlugin (extensibleNotificationPlugins recorder) id <>
6363 mkPlugin dynFlagsPlugins HLS. pluginModifyDynflags
6464 where
@@ -153,80 +153,66 @@ executeCommandHandlers ecs = requestHandler SWorkspaceExecuteCommand execCmd
153153
154154-- ---------------------------------------------------------------------
155155
156- extensiblePlugins :: [(PluginId , PluginDescriptor 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 }
158158 where
159- getPluginDescriptor pid = lookup pid xs
160159 IdeHandlers handlers' = foldMap bakePluginId xs
161160 bakePluginId :: (PluginId , PluginDescriptor IdeState ) -> IdeHandlers
162161 bakePluginId (pid,pluginDesc) = IdeHandlers $ DMap. map
163- (\ (PluginHandler f) -> IdeHandler [(pid,f pid)])
162+ (\ (PluginHandler f) -> IdeHandler [(pid,pluginDesc, f pid)])
164163 hs
165164 where
166165 PluginHandlers hs = HLS. pluginHandlers pluginDesc
167166 handlers = mconcat $ do
168167 (IdeMethod m :=> IdeHandler fs') <- DMap. assocs handlers'
169168 pure $ requestHandler m $ \ ide params -> do
170169 config <- Ide.PluginUtils. getClientConfig
171- let pluginInfo = map (\ (pid,_) -> (pid, getPluginDescriptor pid)) fs'
172- cleanPluginInfo <- collectPluginDescriptors pluginInfo []
173- case cleanPluginInfo of
174- Left err -> pure $ Left err
175- Right pluginInfos -> do
176- let fs = map snd $ filter (\ ((_, desc), _) -> pluginEnabled m params desc config) (zip pluginInfos fs')
177- case nonEmpty fs of
178- Nothing -> pure $ Left $ ResponseError InvalidRequest
179- (" No plugin enabled for " <> T. pack (show m) <> " , available: " <> T. pack (show $ map fst fs))
180- Nothing
181- Just fs -> do
182- let msg e pid = " Exception in plugin " <> T. pack (show pid) <> " while processing " <> T. pack (show m) <> " : " <> T. pack (show e)
183- es <- runConcurrently msg (show m) fs ide params
184- let (errs,succs) = partitionEithers $ toList es
185- case nonEmpty succs of
186- Nothing -> pure $ Left $ combineErrors errs
187- Just xs -> do
188- caps <- LSP. getClientCapabilities
189- pure $ Right $ combineResponses m config caps params xs
190-
191- collectPluginDescriptors :: [(PluginId , Maybe (PluginDescriptor c ))] -> [(PluginId , PluginDescriptor c )] -> LSP. LspM Config (Either ResponseError [(PluginId , PluginDescriptor c )])
192- collectPluginDescriptors ((pid, Nothing ): _) _ = pure $ Left $ ResponseError InvalidRequest
193- (" No plugindescriptor found for " <> pidT <> " , available: " )
194- Nothing
195- where
196- PluginId pidT = pid
197- collectPluginDescriptors ((pid, Just desc): xs) ys = collectPluginDescriptors xs (ys ++ [(pid, desc)])
198- collectPluginDescriptors [] ys = pure $ Right ys
170+ -- Only run plugins that are allowed to run on this request
171+ let fs = filter (\ (_, desc, _) -> pluginEnabled m params desc config) fs'
172+ case nonEmpty fs of
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
180+ Just fs -> do
181+ let msg e pid = " Exception in plugin " <> T. pack (show pid) <> " while processing " <> T. pack (show m) <> " : " <> T. pack (show e)
182+ handlers = fmap (\ (plid,_,handler) -> (plid,handler)) fs
183+ es <- runConcurrently msg (show m) handlers ide params
184+ let (errs,succs) = partitionEithers $ toList es
185+ case nonEmpty succs of
186+ Nothing -> pure $ Left $ combineErrors errs
187+ Just xs -> do
188+ caps <- LSP. getClientCapabilities
189+ pure $ Right $ combineResponses m config caps params xs
199190
200191-- ---------------------------------------------------------------------
201192
202193extensibleNotificationPlugins :: Recorder (WithPriority Log ) -> [(PluginId , PluginDescriptor IdeState )] -> Plugin Config
203194extensibleNotificationPlugins recorder xs = mempty { P. pluginHandlers = handlers }
204195 where
205- getPluginDescriptor pid = lookup pid xs
206196 IdeNotificationHandlers handlers' = foldMap bakePluginId xs
207197 bakePluginId :: (PluginId , PluginDescriptor IdeState ) -> IdeNotificationHandlers
208198 bakePluginId (pid,pluginDesc) = IdeNotificationHandlers $ DMap. map
209- (\ (PluginNotificationHandler f) -> IdeNotificationHandler [(pid,f pid)])
199+ (\ (PluginNotificationHandler f) -> IdeNotificationHandler [(pid,pluginDesc, f pid)])
210200 hs
211201 where PluginNotificationHandlers hs = HLS. pluginNotificationHandlers pluginDesc
212202 handlers = mconcat $ do
213203 (IdeNotification m :=> IdeNotificationHandler fs') <- DMap. assocs handlers'
214204 pure $ notificationHandler m $ \ ide vfs params -> do
215205 config <- Ide.PluginUtils. getClientConfig
216- let pluginInfo = map (\ (pid,_) -> (pid, getPluginDescriptor pid)) fs'
217- cleanPluginInfo <- collectPluginDescriptors pluginInfo []
218- case cleanPluginInfo of
219- Left _ -> pure ()
220- Right pluginInfos -> do
221- let fs = map snd $ filter (\ ((_, desc), _) -> pluginEnabled m params desc config) (zip pluginInfos fs')
222- case nonEmpty fs of
223- Nothing -> do
224- logWith recorder Info LogNoEnabledPlugins
225- pure ()
226- Just fs -> do
227- -- We run the notifications in order, so the core ghcide provider
228- -- (which restarts the shake process) hopefully comes last
229- mapM_ (\ (pid,f) -> otTracedProvider pid (fromString $ show m) $ f ide vfs params) fs
206+ -- Only run plugins that are allowed to run on this request
207+ let fs = filter (\ (_, desc, _) -> pluginEnabled m params desc config) fs'
208+ case nonEmpty fs of
209+ Nothing -> do
210+ logWith recorder Info LogNoEnabledPlugins
211+ pure ()
212+ Just fs -> do
213+ -- We run the notifications in order, so the core ghcide provider
214+ -- (which restarts the shake process) hopefully comes last
215+ mapM_ (\ (pid,_,f) -> otTracedProvider pid (fromString $ show m) $ f ide vfs params) fs
230216
231217-- ---------------------------------------------------------------------
232218
@@ -235,6 +221,7 @@ runConcurrently
235221 => (SomeException -> PluginId -> T. Text )
236222 -> String -- ^ label
237223 -> NonEmpty (PluginId , a -> b -> m (NonEmpty (Either ResponseError d )))
224+ -- ^ Enabled plugin actions that we are allowed to run
238225 -> a
239226 -> b
240227 -> m (NonEmpty (Either ResponseError d ))
@@ -248,11 +235,11 @@ combineErrors xs = ResponseError InternalError (T.pack (show xs)) Nothing
248235
249236-- | Combine the 'PluginHandler' for all plugins
250237newtype IdeHandler (m :: J. Method FromClient Request )
251- = 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 ))))]
252239
253240-- | Combine the 'PluginHandler' for all plugins
254241newtype IdeNotificationHandler (m :: J. Method FromClient Notification )
255- = IdeNotificationHandler [(PluginId , IdeState -> VFS -> MessageParams m -> LSP. LspM Config () )]
242+ = IdeNotificationHandler [(PluginId , PluginDescriptor IdeState , IdeState -> VFS -> MessageParams m -> LSP. LspM Config () )]
256243-- type NotificationHandler (m :: Method FromClient Notification) = MessageParams m -> IO ()`
257244
258245-- | Combine the 'PluginHandlers' for all plugins
0 commit comments