@@ -10,6 +10,7 @@ module Development.IDE.Plugin.HLS
1010 ) where
1111
1212import Control.Exception (SomeException )
13+ import Control.Lens ((^.) )
1314import Control.Monad
1415import qualified Data.Aeson as J
1516import Data.Bifunctor
@@ -21,6 +22,7 @@ import qualified Data.List as List
2122import Data.List.NonEmpty (NonEmpty , nonEmpty , toList )
2223import qualified Data.Map as Map
2324import Data.String
25+ import Data.Text (Text )
2426import qualified Data.Text as T
2527import Development.IDE.Core.Shake hiding (Log )
2628import Development.IDE.Core.Tracing
@@ -33,9 +35,10 @@ import Ide.Plugin.Config
3335import Ide.PluginUtils (getClientConfig )
3436import Ide.Types as HLS
3537import qualified Language.LSP.Server as LSP
36- import Language.LSP.VFS
3738import Language.LSP.Types
3839import qualified Language.LSP.Types as J
40+ import qualified Language.LSP.Types.Lens as LSP
41+ import Language.LSP.VFS
3942import Text.Regex.TDFA.Text ()
4043import UnliftIO (MonadUnliftIO )
4144import UnliftIO.Async (forConcurrently )
@@ -44,20 +47,48 @@ import UnliftIO.Exception (catchAny)
4447-- ---------------------------------------------------------------------
4548--
4649
47- data Log
48- = LogNoEnabledPlugins
49- deriving Show
50+ data Log = LogPluginError ResponseError
51+ deriving Show
5052
5153instance Pretty Log where
5254 pretty = \ case
53- LogNoEnabledPlugins ->
54- " extensibleNotificationPlugins no enabled plugins"
55+ LogPluginError err -> prettyResponseError err
56+
57+ -- various error message specific builders
58+ prettyResponseError :: ResponseError -> Doc a
59+ prettyResponseError err = errorCode <> " :" <+> errorBody
60+ where
61+ errorCode = pretty $ show $ err ^. LSP. code
62+ errorBody = pretty $ err ^. LSP. message
63+
64+ pluginNotEnabled :: SMethod m -> [(PluginId , b , a )] -> Text
65+ pluginNotEnabled method availPlugins = " No plugin enabled for " <> T. pack (show method) <> " , available:\n " <> T. pack (unlines $ map (\ (plid,_,_) -> show plid) availPlugins)
66+
67+ pluginDoesntExist :: PluginId -> Text
68+ pluginDoesntExist (PluginId pid) = " Plugin " <> pid <> " doesn't exist"
69+
70+ commandDoesntExist :: CommandId -> PluginId -> [PluginCommand ideState ] -> Text
71+ commandDoesntExist (CommandId com) (PluginId pid) legalCmds = " Command " <> com <> " isn't defined for plugin " <> pid <> " . Legal commands are:\n " <> T. pack (unlines $ map (show . commandId) legalCmds)
72+
73+ failedToParseArgs :: CommandId -- ^ command that failed to parse
74+ -> PluginId -- ^ Plugin that created the command
75+ -> String -- ^ The JSON Error message
76+ -> J. Value -- ^ The Argument Values
77+ -> Text
78+ failedToParseArgs (CommandId com) (PluginId pid) err arg = " Error while parsing args for " <> com <> " in plugin " <> pid <> " : " <> T. pack err <> " \n arg = " <> T. pack (show arg)
79+
80+ -- | Build a ResponseError and log it before returning to the caller
81+ logAndReturnError :: Recorder (WithPriority Log ) -> ErrorCode -> Text -> LSP. LspT Config IO (Either ResponseError a )
82+ logAndReturnError recorder errCode msg = do
83+ let err = ResponseError errCode msg Nothing
84+ logWith recorder Warning $ LogPluginError err
85+ pure $ Left err
5586
5687-- | Map a set of plugins to the underlying ghcide engine.
5788asGhcIdePlugin :: Recorder (WithPriority Log ) -> IdePlugins IdeState -> Plugin Config
5889asGhcIdePlugin recorder (IdePlugins ls) =
5990 mkPlugin rulesPlugins HLS. pluginRules <>
60- mkPlugin executeCommandPlugins HLS. pluginCommands <>
91+ mkPlugin ( executeCommandPlugins recorder) HLS. pluginCommands <>
6192 mkPlugin (extensiblePlugins recorder) id <>
6293 mkPlugin (extensibleNotificationPlugins recorder) id <>
6394 mkPlugin dynFlagsPlugins HLS. pluginModifyDynflags
@@ -91,11 +122,11 @@ dynFlagsPlugins rs = mempty
91122
92123-- ---------------------------------------------------------------------
93124
94- executeCommandPlugins :: [(PluginId , [PluginCommand IdeState ])] -> Plugin Config
95- executeCommandPlugins ecs = mempty { P. pluginHandlers = executeCommandHandlers ecs }
125+ executeCommandPlugins :: Recorder ( WithPriority Log ) -> [(PluginId , [PluginCommand IdeState ])] -> Plugin Config
126+ executeCommandPlugins recorder ecs = mempty { P. pluginHandlers = executeCommandHandlers recorder ecs }
96127
97- executeCommandHandlers :: [(PluginId , [PluginCommand IdeState ])] -> LSP. Handlers (ServerM Config )
98- executeCommandHandlers ecs = requestHandler SWorkspaceExecuteCommand execCmd
128+ executeCommandHandlers :: Recorder ( WithPriority Log ) -> [(PluginId , [PluginCommand IdeState ])] -> LSP. Handlers (ServerM Config )
129+ executeCommandHandlers recorder ecs = requestHandler SWorkspaceExecuteCommand execCmd
99130 where
100131 pluginMap = Map. fromList ecs
101132
@@ -134,21 +165,15 @@ executeCommandHandlers ecs = requestHandler SWorkspaceExecuteCommand execCmd
134165 Just (plugin, cmd) -> runPluginCommand ide plugin cmd cmdParams
135166
136167 -- Couldn't parse the command identifier
137- _ -> return $ Left $ ResponseError InvalidParams " Invalid command identifier " Nothing
168+ _ -> logAndReturnError recorder InvalidParams " Invalid command Identifier "
138169
139- runPluginCommand ide p@ ( PluginId p') com@ ( CommandId com') arg =
170+ runPluginCommand ide p com arg =
140171 case Map. lookup p pluginMap of
141- Nothing -> return
142- (Left $ ResponseError InvalidRequest (" Plugin " <> p' <> " doesn't exist" ) Nothing )
172+ Nothing -> logAndReturnError recorder InvalidRequest (pluginDoesntExist p)
143173 Just xs -> case List. find ((com == ) . commandId) xs of
144- Nothing -> return $ Left $
145- ResponseError InvalidRequest (" Command " <> com' <> " isn't defined for plugin " <> p'
146- <> " . Legal commands are: " <> T. pack(show $ map commandId xs)) Nothing
174+ Nothing -> logAndReturnError recorder InvalidRequest (commandDoesntExist com p xs)
147175 Just (PluginCommand _ _ f) -> case J. fromJSON arg of
148- J. Error err -> return $ Left $
149- ResponseError InvalidParams (" error while parsing args for " <> com' <> " in plugin " <> p'
150- <> " : " <> T. pack err
151- <> " \n arg = " <> T. pack (show arg)) Nothing
176+ J. Error err -> logAndReturnError recorder InvalidParams (failedToParseArgs com p err arg)
152177 J. Success a -> f ide a
153178
154179-- ---------------------------------------------------------------------
@@ -169,19 +194,15 @@ extensiblePlugins recorder xs = mempty { P.pluginHandlers = handlers }
169194 config <- Ide.PluginUtils. getClientConfig
170195 -- Only run plugins that are allowed to run on this request
171196 let fs = filter (\ (_, desc, _) -> pluginEnabled m params desc config) fs'
197+ -- Clients generally don't display ResponseErrors so instead we log any that we come across
172198 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
199+ Nothing -> logAndReturnError recorder InvalidRequest (pluginNotEnabled m fs')
180200 Just fs -> do
181201 let msg e pid = " Exception in plugin " <> T. pack (show pid) <> " while processing " <> T. pack (show m) <> " : " <> T. pack (show e)
182202 handlers = fmap (\ (plid,_,handler) -> (plid,handler)) fs
183203 es <- runConcurrently msg (show m) handlers ide params
184204 let (errs,succs) = partitionEithers $ toList es
205+ unless (null errs) $ forM_ errs $ \ err -> logWith recorder Error $ LogPluginError err
185206 case nonEmpty succs of
186207 Nothing -> pure $ Left $ combineErrors errs
187208 Just xs -> do
@@ -206,9 +227,7 @@ extensibleNotificationPlugins recorder xs = mempty { P.pluginHandlers = handlers
206227 -- Only run plugins that are allowed to run on this request
207228 let fs = filter (\ (_, desc, _) -> pluginEnabled m params desc config) fs'
208229 case nonEmpty fs of
209- Nothing -> do
210- logWith recorder Info LogNoEnabledPlugins
211- pure ()
230+ Nothing -> void $ logAndReturnError recorder InvalidRequest (pluginNotEnabled m fs')
212231 Just fs -> do
213232 -- We run the notifications in order, so the core ghcide provider
214233 -- (which restarts the shake process) hopefully comes last
@@ -227,7 +246,7 @@ runConcurrently
227246 -> m (NonEmpty (Either ResponseError d ))
228247runConcurrently msg method fs a b = fmap join $ forConcurrently fs $ \ (pid,f) -> otTracedProvider pid (fromString method) $ do
229248 f a b
230- `catchAny` (\ e -> pure $ pure $ Left $ ResponseError InternalError (msg e pid) Nothing )
249+ `catchAny` (\ e -> pure $ pure $ Left $ ResponseError InternalError (msg e pid) Nothing )
231250
232251combineErrors :: [ResponseError ] -> ResponseError
233252combineErrors [x] = x
0 commit comments