Skip to content

Commit e5f6931

Browse files
authored
Improve no plugin messages (#3864)
1 parent 0be6fa7 commit e5f6931

File tree

10 files changed

+281
-211
lines changed

10 files changed

+281
-211
lines changed

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

Lines changed: 31 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ import qualified Data.List as List
2323
import Data.List.NonEmpty (NonEmpty, nonEmpty, toList)
2424
import qualified Data.List.NonEmpty as NE
2525
import qualified Data.Map as Map
26+
import Data.Maybe (mapMaybe)
2627
import Data.Some
2728
import Data.String
2829
import Data.Text (Text)
@@ -36,6 +37,7 @@ import qualified Development.IDE.Plugin as P
3637
import Ide.Logger
3738
import Ide.Plugin.Config
3839
import Ide.Plugin.Error
40+
import Ide.Plugin.HandleRequestTypes
3941
import Ide.PluginUtils (getClientConfig)
4042
import Ide.Types as HLS
4143
import Language.LSP.Protocol.Message
@@ -65,23 +67,29 @@ instance Pretty Log where
6567
LogResponseError (PluginId pId) err ->
6668
pretty pId <> ":" <+> pretty err
6769
LogNoPluginForMethod (Some method) ->
68-
"No plugin enabled for " <> pretty method
70+
"No plugin handles this " <> pretty method <> " request."
6971
LogInvalidCommandIdentifier-> "Invalid command identifier"
7072
ExceptionInPlugin plId (Some method) exception ->
7173
"Exception in plugin " <> viaShow plId <> " while processing "
7274
<> pretty method <> ": " <> viaShow exception
7375
instance Show Log where show = renderString . layoutCompact . pretty
7476

75-
noPluginEnabled :: Recorder (WithPriority Log) -> SMethod m -> [PluginId] -> IO (Either ResponseError c)
76-
noPluginEnabled recorder m fs' = do
77+
noPluginHandles :: Recorder (WithPriority Log) -> SMethod m -> [(PluginId, HandleRequestResult)] -> IO (Either ResponseError c)
78+
noPluginHandles recorder m fs' = do
7779
logWith recorder Warning (LogNoPluginForMethod $ Some m)
7880
let err = ResponseError (InR ErrorCodes_MethodNotFound) msg Nothing
79-
msg = pluginNotEnabled m fs'
81+
msg = noPluginHandlesMsg m fs'
8082
return $ Left err
81-
where pluginNotEnabled :: SMethod m -> [PluginId] -> Text
82-
pluginNotEnabled method availPlugins =
83-
"No plugin enabled for " <> T.pack (show method) <> ", potentially available: "
84-
<> (T.intercalate ", " $ map (\(PluginId plid) -> plid) availPlugins)
83+
where noPluginHandlesMsg :: SMethod m -> [(PluginId, HandleRequestResult)] -> Text
84+
noPluginHandlesMsg method [] = "No plugins are available to handle this " <> T.pack (show method) <> " request."
85+
noPluginHandlesMsg method availPlugins =
86+
"No plugins are available to handle this " <> T.pack (show method) <> " request.\n Plugins installed for this method, but not available to handle this request are:\n"
87+
<> (T.intercalate "\n" $
88+
map (\(PluginId plid, pluginStatus) ->
89+
plid
90+
<> " "
91+
<> (renderStrict . layoutCompact . pretty) pluginStatus)
92+
availPlugins)
8593

8694
pluginDoesntExist :: PluginId -> Text
8795
pluginDoesntExist (PluginId pid) = "Plugin " <> pid <> " doesn't exist"
@@ -213,8 +221,8 @@ executeCommandHandlers recorder ecs = requestHandler SMethod_WorkspaceExecuteCom
213221
res <- runExceptT (f ide a) `catchAny` -- See Note [Exception handling in plugins]
214222
(\e -> pure $ Left $ PluginInternalError (exceptionInPlugin p SMethod_WorkspaceExecuteCommand e))
215223
case res of
216-
(Left (PluginRequestRefused _)) ->
217-
liftIO $ noPluginEnabled recorder SMethod_WorkspaceExecuteCommand (fst <$> ecs)
224+
(Left (PluginRequestRefused r)) ->
225+
liftIO $ noPluginHandles recorder SMethod_WorkspaceExecuteCommand [(p,DoesNotHandleRequest r)]
218226
(Left pluginErr) -> do
219227
liftIO $ logErrors recorder [(p, pluginErr)]
220228
pure $ Left $ toResponseError (p, pluginErr)
@@ -236,11 +244,13 @@ extensiblePlugins recorder plugins = mempty { P.pluginHandlers = handlers }
236244
(IdeMethod m :=> IdeHandler fs') <- DMap.assocs handlers'
237245
pure $ requestHandler m $ \ide params -> do
238246
config <- Ide.PluginUtils.getClientConfig
239-
-- Only run plugins that are allowed to run on this request
240-
let fs = filter (\(_, desc, _) -> pluginEnabled m params desc config) fs'
247+
-- Only run plugins that are allowed to run on this request, save the
248+
-- list of disabled plugins incase that's all we have
249+
let (fs, dfs) = List.partition (\(_, desc, _) -> handlesRequest m params desc config == HandlesRequest) fs'
250+
let disabledPluginsReason = (\(x, desc, _) -> (x, handlesRequest m params desc config)) <$> dfs
241251
-- Clients generally don't display ResponseErrors so instead we log any that we come across
242252
case nonEmpty fs of
243-
Nothing -> liftIO $ noPluginEnabled recorder m ((\(x, _, _) -> x) <$> fs')
253+
Nothing -> liftIO $ noPluginHandles recorder m disabledPluginsReason
244254
Just neFs -> do
245255
let plidsAndHandlers = fmap (\(plid,_,handler) -> (plid,handler)) neFs
246256
es <- runConcurrently exceptionInPlugin m plidsAndHandlers ide params
@@ -251,9 +261,12 @@ extensiblePlugins recorder plugins = mempty { P.pluginHandlers = handlers }
251261
Nothing -> do
252262
let noRefused (_, PluginRequestRefused _) = False
253263
noRefused (_, _) = True
254-
filteredErrs = filter noRefused errs
255-
case nonEmpty filteredErrs of
256-
Nothing -> liftIO $ noPluginEnabled recorder m ((\(x, _, _) -> x) <$> fs')
264+
(asErrors, asRefused) = List.partition noRefused errs
265+
convertPRR (pId, PluginRequestRefused r) = Just (pId, DoesNotHandleRequest r)
266+
convertPRR _ = Nothing
267+
asRefusedReason = mapMaybe convertPRR asRefused
268+
case nonEmpty asErrors of
269+
Nothing -> liftIO $ noPluginHandles recorder m (disabledPluginsReason <> asRefusedReason)
257270
Just xs -> pure $ Left $ combineErrors xs
258271
Just xs -> do
259272
pure $ Right $ combineResponses m config caps params xs
@@ -274,8 +287,8 @@ extensibleNotificationPlugins recorder xs = mempty { P.pluginHandlers = handlers
274287
(IdeNotification m :=> IdeNotificationHandler fs') <- DMap.assocs handlers'
275288
pure $ notificationHandler m $ \ide vfs params -> do
276289
config <- Ide.PluginUtils.getClientConfig
277-
-- Only run plugins that are allowed to run on this request
278-
let fs = filter (\(_, desc, _) -> pluginEnabled m params desc config) fs'
290+
-- Only run plugins that are enabled for this request
291+
let fs = filter (\(_, desc, _) -> handlesRequest m params desc config == HandlesRequest) fs'
279292
case nonEmpty fs of
280293
Nothing -> do
281294
logWith recorder Warning (LogNoPluginForMethod $ Some m)

ghcide/test/exe/ExceptionTests.hs

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ import GHC.Base (coerce)
1818
import Ide.Logger (Logger, Recorder,
1919
WithPriority, cmapWithPrio)
2020
import Ide.Plugin.Error
21+
import Ide.Plugin.HandleRequestTypes (RejectionReason (DisabledGlobally))
2122
import Ide.PluginUtils (idePluginsToPluginDesc,
2223
pluginDescToIdePlugins)
2324
import Ide.Types
@@ -106,9 +107,9 @@ tests recorder logger = do
106107
_ -> liftIO $ assertFailure $ "We should have had an empty list" <> show lens]
107108

108109
, testGroup "Testing PluginError order..."
109-
[ pluginOrderTestCase recorder logger "InternalError over InvalidParams" PluginInternalError PluginInvalidParams
110-
, pluginOrderTestCase recorder logger "InvalidParams over InvalidUserState" PluginInvalidParams PluginInvalidUserState
111-
, pluginOrderTestCase recorder logger "InvalidUserState over RequestRefused" PluginInvalidUserState PluginRequestRefused
110+
[ pluginOrderTestCase recorder logger "InternalError over InvalidParams" (PluginInternalError "error test") (PluginInvalidParams "error test")
111+
, pluginOrderTestCase recorder logger "InvalidParams over InvalidUserState" (PluginInvalidParams "error test") (PluginInvalidUserState "error test")
112+
, pluginOrderTestCase recorder logger "InvalidUserState over RequestRefused" (PluginInvalidUserState "error test") (PluginRequestRefused DisabledGlobally)
112113
]
113114
]
114115

@@ -132,24 +133,24 @@ testingLite recorder logger plugins =
132133
, IDE.argsIdeOptions = ideOptions
133134
}
134135

135-
pluginOrderTestCase :: Recorder (WithPriority Log) -> Logger -> TestName -> (T.Text -> PluginError) -> (T.Text -> PluginError) -> TestTree
136+
pluginOrderTestCase :: Recorder (WithPriority Log) -> Logger -> TestName -> PluginError -> PluginError -> TestTree
136137
pluginOrderTestCase recorder logger msg err1 err2 =
137138
testCase msg $ do
138139
let pluginId = "error-order-test"
139140
plugins = pluginDescToIdePlugins $
140141
[ (defaultPluginDescriptor pluginId "")
141142
{ pluginHandlers = mconcat
142143
[ mkPluginHandler SMethod_TextDocumentCodeLens $ \_ _ _-> do
143-
throwError $ err1 "error test"
144+
throwError err1
144145
,mkPluginHandler SMethod_TextDocumentCodeLens $ \_ _ _-> do
145-
throwError $ err2 "error test"
146+
throwError err2
146147
]
147148
}]
148149
testIde recorder (testingLite recorder logger plugins) $ do
149150
doc <- createDoc "A.hs" "haskell" "module A where"
150151
waitForProgressDone
151152
(view L.result -> lens) <- request SMethod_TextDocumentCodeLens (CodeLensParams Nothing Nothing doc)
152153
case lens of
153-
Left re | toResponseError (pluginId, err1 "error test") == re -> pure ()
154+
Left re | toResponseError (pluginId, err1) == re -> pure ()
154155
| otherwise -> liftIO $ assertFailure "We caught an error, but it wasn't ours!"
155156
_ -> liftIO $ assertFailure $ show lens

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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,7 @@ library
3838
Ide.Plugin.Config
3939
Ide.Plugin.ConfigUtils
4040
Ide.Plugin.Error
41+
Ide.Plugin.HandleRequestTypes
4142
Ide.Plugin.Properties
4243
Ide.Plugin.RangeMap
4344
Ide.Plugin.Resolve

hls-plugin-api/src/Ide/Plugin/Error.hs

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -11,11 +11,12 @@ module Ide.Plugin.Error (
1111
getNormalizedFilePathE,
1212
) where
1313

14-
import Control.Monad.Extra (maybeM)
15-
import Control.Monad.Trans.Class (lift)
16-
import Control.Monad.Trans.Except (ExceptT (..), throwE)
17-
import qualified Data.Text as T
14+
import Control.Monad.Extra (maybeM)
15+
import Control.Monad.Trans.Class (lift)
16+
import Control.Monad.Trans.Except (ExceptT (..), throwE)
17+
import qualified Data.Text as T
1818
import Ide.Logger
19+
import Ide.Plugin.HandleRequestTypes (RejectionReason)
1920
import Language.LSP.Protocol.Types
2021

2122
-- ----------------------------------------------------------------------------
@@ -79,13 +80,13 @@ data PluginError
7980
| PluginInvalidUserState T.Text
8081
-- |PluginRequestRefused allows your handler to inspect a request before
8182
-- rejecting it. In effect it allows your plugin to act make a secondary
82-
-- `pluginEnabled` decision after receiving the request. This should only be
83+
-- `handlesRequest` decision after receiving the request. This should only be
8384
-- used if the decision to accept the request can not be made in
84-
-- `pluginEnabled`.
85+
-- `handlesRequest`.
8586
--
8687
-- This error will be with Debug. If it's the only response to a request,
87-
-- HLS will respond as if no plugins passed the `pluginEnabled` stage.
88-
| PluginRequestRefused T.Text
88+
-- HLS will respond as if no plugins passed the `handlesRequest` stage.
89+
| PluginRequestRefused RejectionReason
8990
-- |PluginRuleFailed should be thrown when a Rule your response depends on
9091
-- fails.
9192
--
Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,46 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
3+
module Ide.Plugin.HandleRequestTypes where
4+
5+
import Data.Text
6+
import Prettyprinter
7+
8+
-- | Reasons why a plugin could reject a specific request.
9+
data RejectionReason =
10+
-- | The resolve request is not meant for this plugin or handler. The text
11+
-- field should contain the identifier for the plugin who owns this resolve
12+
-- request.
13+
NotResolveOwner Text
14+
-- | The plugin is disabled globally in the users config.
15+
| DisabledGlobally
16+
-- | The feature in the plugin that responds to this request is disabled in
17+
-- the users config
18+
| FeatureDisabled
19+
-- | This plugin is not the formatting provider selected in the users config.
20+
-- The text should be the formatting provider in your config.
21+
| NotFormattingProvider Text
22+
-- | This plugin does not support the file type. The text field here should
23+
-- contain the filetype of the rejected request.
24+
| DoesNotSupportFileType Text
25+
deriving (Eq)
26+
27+
-- | Whether a plugin will handle a request or not.
28+
data HandleRequestResult = HandlesRequest | DoesNotHandleRequest RejectionReason
29+
deriving (Eq)
30+
31+
instance Pretty HandleRequestResult where
32+
pretty HandlesRequest = "handles this request"
33+
pretty (DoesNotHandleRequest reason) = pretty reason
34+
35+
instance Pretty RejectionReason where
36+
pretty (NotResolveOwner s) = "does not handle resolve requests for " <> pretty s <> ")."
37+
pretty DisabledGlobally = "is disabled globally in your config."
38+
pretty FeatureDisabled = "'s feature that handles this request is disabled in your config."
39+
pretty (NotFormattingProvider s) = "is not the formatting provider ("<> pretty s<>") you chose in your config."
40+
pretty (DoesNotSupportFileType s) = "does not support " <> pretty s <> " filetypes)."
41+
42+
-- We always want to keep the leftmost disabled reason
43+
instance Semigroup HandleRequestResult where
44+
HandlesRequest <> HandlesRequest = HandlesRequest
45+
DoesNotHandleRequest r <> _ = DoesNotHandleRequest r
46+
_ <> DoesNotHandleRequest r = DoesNotHandleRequest r

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ module Ide.PluginUtils
2020
getClientConfig,
2121
getPluginConfig,
2222
configForPlugin,
23-
pluginEnabled,
23+
handlesRequest,
2424
extractTextInRange,
2525
fullRange,
2626
mkLspCommand,

0 commit comments

Comments
 (0)