@@ -51,15 +51,19 @@ import UnliftIO.Exception (catchAny)
5151--
5252
5353data Log
54- = LogPluginError PluginId ResponseError
54+ = LogPluginError PluginId ResponseError
5555 | LogNoPluginForMethod (Some SMethod )
5656 | LogInvalidCommandIdentifier
57+ | ExceptionInPlugin PluginId (Some SMethod ) SomeException
58+
5759instance Pretty Log where
5860 pretty = \ case
5961 LogPluginError (PluginId pId) err -> pretty pId <> " :" <+> prettyResponseError err
6062 LogNoPluginForMethod (Some method) ->
6163 " No plugin enabled for " <> pretty (show method)
6264 LogInvalidCommandIdentifier -> " Invalid command identifier"
65+ ExceptionInPlugin plId (Some method) exception ->
66+ " Exception in plugin " <> viaShow plId <> " while processing " <> viaShow method <> " : " <> viaShow exception
6367
6468instance Show Log where show = renderString . layoutCompact . pretty
6569
@@ -92,13 +96,24 @@ failedToParseArgs (CommandId com) (PluginId pid) err arg =
9296 " Error while parsing args for " <> com <> " in plugin " <> pid <> " : "
9397 <> T. pack err <> " , arg = " <> T. pack (show arg)
9498
99+ exceptionInPlugin :: PluginId -> SMethod m -> SomeException -> Text
100+ exceptionInPlugin plId method exception =
101+ " Exception in plugin " <> T. pack (show plId) <> " while processing " <> T. pack (show method) <> " : " <> T. pack (show exception)
102+
95103-- | Build a ResponseError and log it before returning to the caller
96104logAndReturnError :: Recorder (WithPriority Log ) -> PluginId -> (LSPErrorCodes |? ErrorCodes ) -> Text -> LSP. LspT Config IO (Either ResponseError a )
97105logAndReturnError recorder p errCode msg = do
98106 let err = ResponseError errCode msg Nothing
99107 logWith recorder Warning $ LogPluginError p err
100108 pure $ Left err
101109
110+ -- | Logs the provider error before returning it to the caller
111+ logAndReturnError' :: Recorder (WithPriority Log ) -> (LSPErrorCodes |? ErrorCodes ) -> Log -> LSP. LspT Config IO (Either ResponseError a )
112+ logAndReturnError' recorder errCode msg = do
113+ let err = ResponseError errCode (fromString $ show msg) Nothing
114+ logWith recorder Warning $ msg
115+ pure $ Left err
116+
102117-- | Map a set of plugins to the underlying ghcide engine.
103118asGhcIdePlugin :: Recorder (WithPriority Log ) -> IdePlugins IdeState -> Plugin Config
104119asGhcIdePlugin recorder (IdePlugins ls) =
@@ -177,9 +192,9 @@ executeCommandHandlers recorder ecs = requestHandler SMethod_WorkspaceExecuteCom
177192 -- If we have a command, continue to execute it
178193 Just (Command _ innerCmdId innerArgs)
179194 -> execCmd ide (ExecuteCommandParams Nothing innerCmdId innerArgs)
180- Nothing -> return $ Right $ InL A. Null
195+ Nothing -> return $ Right $ InR Null
181196
182- A. Error _str -> return $ Right $ InL A. Null
197+ A. Error _str -> return $ Right $ InR Null
183198
184199 -- Just an ordinary HIE command
185200 Just (plugin, cmd) -> runPluginCommand ide plugin cmd cmdParams
@@ -197,7 +212,9 @@ executeCommandHandlers recorder ecs = requestHandler SMethod_WorkspaceExecuteCom
197212 Nothing -> logAndReturnError recorder p (InR ErrorCodes_InvalidRequest ) (commandDoesntExist com p xs)
198213 Just (PluginCommand _ _ f) -> case A. fromJSON arg of
199214 A. Error err -> logAndReturnError recorder p (InR ErrorCodes_InvalidParams ) (failedToParseArgs com p err arg)
200- A. Success a -> fmap InL <$> f ide a
215+ A. Success a ->
216+ f ide a `catchAny` -- See Note [Exception handling in plugins]
217+ (\ e -> logAndReturnError' recorder (InR ErrorCodes_InternalError ) (ExceptionInPlugin p (Some SMethod_WorkspaceApplyEdit ) e))
201218
202219-- ---------------------------------------------------------------------
203220
@@ -225,9 +242,8 @@ extensiblePlugins recorder xs = mempty { P.pluginHandlers = handlers }
225242 msg = pluginNotEnabled m fs'
226243 return $ Left err
227244 Just fs -> do
228- let msg e pid = " Exception in plugin " <> T. pack (show pid) <> " while processing " <> T. pack (show m) <> " : " <> T. pack (show e)
229- handlers = fmap (\ (plid,_,handler) -> (plid,handler)) fs
230- es <- runConcurrently msg (show m) handlers ide params
245+ let handlers = fmap (\ (plid,_,handler) -> (plid,handler)) fs
246+ es <- runConcurrently exceptionInPlugin m handlers ide params
231247
232248 let (errs,succs) = partitionEithers $ toList $ join $ NE. zipWith (\ (pId,_) -> fmap (first (pId,))) handlers es
233249 unless (null errs) $ forM_ errs $ \ (pId, err) ->
@@ -261,22 +277,25 @@ extensibleNotificationPlugins recorder xs = mempty { P.pluginHandlers = handlers
261277 Just fs -> do
262278 -- We run the notifications in order, so the core ghcide provider
263279 -- (which restarts the shake process) hopefully comes last
264- mapM_ (\ (pid,_,f) -> otTracedProvider pid (fromString $ show m) $ f ide vfs params) fs
280+ mapM_ (\ (pid,_,f) -> otTracedProvider pid (fromString $ show m) $ f ide vfs params
281+ `catchAny` -- See Note [Exception handling in plugins]
282+ (\ e -> logWith recorder Warning (ExceptionInPlugin pid (Some m) e))) fs
283+
265284
266285-- ---------------------------------------------------------------------
267286
268287runConcurrently
269288 :: MonadUnliftIO m
270- => (SomeException -> PluginId -> T. Text )
271- -> String -- ^ label
289+ => (PluginId -> SMethod method -> SomeException -> T. Text )
290+ -> SMethod method -- ^ Method (used for errors and tracing)
272291 -> NonEmpty (PluginId , a -> b -> m (NonEmpty (Either ResponseError d )))
273292 -- ^ Enabled plugin actions that we are allowed to run
274293 -> a
275294 -> b
276295 -> m (NonEmpty (NonEmpty (Either ResponseError d )))
277- runConcurrently msg method fs a b = forConcurrently fs $ \ (pid,f) -> otTracedProvider pid (fromString method) $ do
278- f a b
279- `catchAny` (\ e -> pure $ pure $ Left $ ResponseError (InR ErrorCodes_InternalError ) (msg e pid) Nothing )
296+ runConcurrently msg method fs a b = forConcurrently fs $ \ (pid,f) -> otTracedProvider pid (fromString ( show method) ) $ do
297+ f a b -- See Note [Exception handling in plugins]
298+ `catchAny` (\ e -> pure $ pure $ Left $ ResponseError (InR ErrorCodes_InternalError ) (msg pid method e ) Nothing )
280299
281300combineErrors :: [ResponseError ] -> ResponseError
282301combineErrors [x] = x
@@ -308,3 +327,16 @@ instance Semigroup IdeNotificationHandlers where
308327 go _ (IdeNotificationHandler a) (IdeNotificationHandler b) = IdeNotificationHandler (a <> b)
309328instance Monoid IdeNotificationHandlers where
310329 mempty = IdeNotificationHandlers mempty
330+
331+ {- Note [Exception handling in plugins]
332+ Plugins run in LspM, and so have access to IO. This means they are likely to
333+ throw exceptions, even if only by accident or through calling libraries that
334+ throw exceptions. Ultimately, we're running a bunch of less-trusted IO code,
335+ so we should be robust to it throwing.
336+
337+ We don't want these to bring down HLS. So we catch and log exceptions wherever
338+ we run a handler defined in a plugin.
339+
340+ The flip side of this is that it's okay for plugins to throw exceptions as a
341+ way of signalling failure!
342+ -}
0 commit comments