@@ -58,8 +58,8 @@ 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 HLS. pluginHandlers <>
62- mkPlugin (extensibleNotificationPlugins recorder) HLS. pluginNotificationHandlers <>
61+ mkPlugin ( extensiblePlugins recorder) id <>
62+ mkPlugin (extensibleNotificationPlugins recorder) id <>
6363 mkPlugin dynFlagsPlugins HLS. pluginModifyDynflags
6464 where
6565
@@ -153,55 +153,66 @@ executeCommandHandlers ecs = requestHandler SWorkspaceExecuteCommand execCmd
153153
154154-- ---------------------------------------------------------------------
155155
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 }
158158 where
159159 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)])
163163 hs
164+ where
165+ PluginHandlers hs = HLS. pluginHandlers pluginDesc
164166 handlers = mconcat $ do
165167 (IdeMethod m :=> IdeHandler fs') <- DMap. assocs handlers'
166168 pure $ requestHandler m $ \ ide params -> do
167169 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'
169172 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
173180 Just fs -> do
174181 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
176184 let (errs,succs) = partitionEithers $ toList es
177185 case nonEmpty succs of
178186 Nothing -> pure $ Left $ combineErrors errs
179187 Just xs -> do
180188 caps <- LSP. getClientCapabilities
181189 pure $ Right $ combineResponses m config caps params xs
190+
182191-- ---------------------------------------------------------------------
183192
184- extensibleNotificationPlugins :: Recorder (WithPriority Log ) -> [(PluginId , PluginNotificationHandlers IdeState )] -> Plugin Config
193+ extensibleNotificationPlugins :: Recorder (WithPriority Log ) -> [(PluginId , PluginDescriptor IdeState )] -> Plugin Config
185194extensibleNotificationPlugins recorder xs = mempty { P. pluginHandlers = handlers }
186195 where
187196 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)])
191200 hs
201+ where PluginNotificationHandlers hs = HLS. pluginNotificationHandlers pluginDesc
192202 handlers = mconcat $ do
193203 (IdeNotification m :=> IdeNotificationHandler fs') <- DMap. assocs handlers'
194204 pure $ notificationHandler m $ \ ide vfs params -> do
195205 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'
197208 case nonEmpty fs of
198209 Nothing -> do
199- logWith recorder Info LogNoEnabledPlugins
200- pure ()
210+ logWith recorder Info LogNoEnabledPlugins
211+ pure ()
201212 Just fs -> do
202213 -- We run the notifications in order, so the core ghcide provider
203214 -- (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
205216
206217-- ---------------------------------------------------------------------
207218
@@ -210,6 +221,7 @@ runConcurrently
210221 => (SomeException -> PluginId -> T. Text )
211222 -> String -- ^ label
212223 -> NonEmpty (PluginId , a -> b -> m (NonEmpty (Either ResponseError d )))
224+ -- ^ Enabled plugin actions that we are allowed to run
213225 -> a
214226 -> b
215227 -> m (NonEmpty (Either ResponseError d ))
@@ -223,11 +235,11 @@ combineErrors xs = ResponseError InternalError (T.pack (show xs)) Nothing
223235
224236-- | Combine the 'PluginHandler' for all plugins
225237newtype 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 ))))]
227239
228240-- | Combine the 'PluginHandler' for all plugins
229241newtype 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 () )]
231243-- type NotificationHandler (m :: Method FromClient Notification) = MessageParams m -> IO ()`
232244
233245-- | Combine the 'PluginHandlers' for all plugins
0 commit comments