9
9
{-# LANGUAGE RankNTypes #-}
10
10
{-# LANGUAGE TypeInType #-}
11
11
{-# LANGUAGE TypeOperators #-}
12
+ {-# LANGUAGE TypeApplications #-}
12
13
13
14
module Language.LSP.Test.Session
14
15
( Session (.. )
@@ -43,8 +44,6 @@ import Control.Lens hiding (List, Empty)
43
44
import Control.Monad
44
45
import Control.Monad.Catch (MonadThrow )
45
46
import Control.Monad.Except
46
- import Control.Monad.IO.Class
47
- import Control.Monad.Trans.Class
48
47
#if __GLASGOW_HASKELL__ == 806
49
48
import Control.Monad.Fail
50
49
#endif
@@ -54,7 +53,9 @@ import Control.Monad.Trans.State (StateT, runStateT, execState)
54
53
import qualified Control.Monad.Trans.State as State
55
54
import qualified Data.ByteString.Lazy.Char8 as B
56
55
import Data.Aeson hiding (Error , Null )
56
+ import qualified Data.Aeson as J
57
57
import Data.Aeson.Encode.Pretty
58
+ import Data.Aeson.Lens ()
58
59
import Data.Conduit as Conduit
59
60
import Data.Conduit.Parser as Parser
60
61
import Data.Default
@@ -84,6 +85,8 @@ import System.Timeout ( timeout )
84
85
import Data.IORef
85
86
import Colog.Core (LogAction (.. ), WithSeverity (.. ), Severity (.. ))
86
87
import Data.Row
88
+ import Data.String (fromString )
89
+ import Data.Either (partitionEithers )
87
90
88
91
-- | A session representing one instance of launching and connecting to a server.
89
92
--
@@ -112,20 +115,26 @@ data SessionConfig = SessionConfig
112
115
-- ^ Trace the messages sent and received to stdout, defaults to False.
113
116
-- Can be overriden with the environment variable @LSP_TEST_LOG_MESSAGES@.
114
117
, logColor :: Bool -- ^ Add ANSI color to the logged messages, defaults to True.
115
- , lspConfig :: Maybe Value -- ^ The initial LSP config as JSON value, defaults to Nothing.
118
+ , lspConfig :: Value
119
+ -- ^ The initial LSP config as JSON value, defaults to Null.
120
+ -- This should include the config section for the server if it has one, i.e. if
121
+ -- the server has a 'mylang' config section, then the config should be an object
122
+ -- with a 'mylang' key whose value is the actual config for the server. You
123
+ -- can also include other config sections if your server may request those.
116
124
, ignoreLogNotifications :: Bool
117
- -- ^ Whether or not to ignore 'Language.LSP.Types.ShowMessageNotification' and
118
- -- 'Language.LSP.Types.LogMessageNotification', defaults to False.
119
- --
120
- -- @since 0.9.0.0
125
+ -- ^ Whether or not to ignore @window/showMessage@ and @window/logMessage@ notifications
126
+ -- from the server, defaults to True.
127
+ , ignoreConfigurationRequests :: Bool
128
+ -- ^ Whether or not to ignore @workspace/configuration@ requests from the server,
129
+ -- defaults to True.
121
130
, initialWorkspaceFolders :: Maybe [WorkspaceFolder ]
122
131
-- ^ The initial workspace folders to send in the @initialize@ request.
123
132
-- Defaults to Nothing.
124
133
}
125
134
126
135
-- | The configuration used in 'Language.LSP.Test.runSession'.
127
136
defaultConfig :: SessionConfig
128
- defaultConfig = SessionConfig 60 False False True Nothing False Nothing
137
+ defaultConfig = SessionConfig 60 False False True J. Null True True Nothing
129
138
130
139
instance Default SessionConfig where
131
140
def = defaultConfig
@@ -179,6 +188,7 @@ data SessionState = SessionState
179
188
-- Used for providing exception information
180
189
, lastReceivedMessage :: ! (Maybe FromServerMessage )
181
190
, curDynCaps :: ! (Map. Map T. Text SomeRegistration )
191
+ , curLspConfig :: Value
182
192
-- ^ The capabilities that the server has dynamically registered with us so
183
193
-- far
184
194
, curProgressSessions :: ! (Set. Set ProgressToken )
@@ -227,15 +237,9 @@ runSessionMonad context state (Session session) = runReaderT (runStateT conduit
227
237
228
238
chanSource = do
229
239
msg <- liftIO $ readChan (messageChan context)
230
- unless (ignoreLogNotifications (config context) && isLogNotification msg) $
231
- yield msg
240
+ yield msg
232
241
chanSource
233
242
234
- isLogNotification (ServerMessage (FromServerMess SMethod_WindowShowMessage _)) = True
235
- isLogNotification (ServerMessage (FromServerMess SMethod_WindowLogMessage _)) = True
236
- isLogNotification (ServerMessage (FromServerMess SMethod_WindowShowDocument _)) = True
237
- isLogNotification _ = False
238
-
239
243
watchdog :: ConduitM SessionMessage FromServerMessage (StateT SessionState (ReaderT SessionContext IO )) ()
240
244
watchdog = Conduit. awaitForever $ \ msg -> do
241
245
curId <- getCurTimeoutId
@@ -273,7 +277,7 @@ runSession' serverIn serverOut mServerProc serverHandler config caps rootDir exi
273
277
mainThreadId <- myThreadId
274
278
275
279
let context = SessionContext serverIn absRootDir messageChan timeoutIdVar reqMap initRsp config caps
276
- initState vfs = SessionState 0 vfs mempty False Nothing mempty mempty
280
+ initState vfs = SessionState 0 vfs mempty False Nothing mempty (lspConfig config) mempty
277
281
runSession' ses = initVFS $ \ vfs -> runSessionMonad context (initState vfs) ses
278
282
279
283
errorHandler = throwTo mainThreadId :: SessionException -> IO ()
@@ -302,17 +306,44 @@ runSession' serverIn serverOut mServerProc serverHandler config caps rootDir exi
302
306
303
307
updateStateC :: ConduitM FromServerMessage FromServerMessage (StateT SessionState (ReaderT SessionContext IO )) ()
304
308
updateStateC = awaitForever $ \ msg -> do
309
+ context <- ask @ SessionContext
305
310
updateState msg
306
- respond msg
307
- yield msg
308
- where
309
- respond :: (MonadIO m , HasReader SessionContext m ) => FromServerMessage -> m ()
310
- respond (FromServerMess SMethod_WindowWorkDoneProgressCreate req) =
311
+ case msg of
312
+ FromServerMess SMethod_WindowWorkDoneProgressCreate req ->
311
313
sendMessage $ TResponseMessage " 2.0" (Just $ req ^. L. id ) (Right Null )
312
- respond ( FromServerMess SMethod_WorkspaceApplyEdit r) = do
314
+ FromServerMess SMethod_WorkspaceApplyEdit r -> do
313
315
sendMessage $ TResponseMessage " 2.0" (Just $ r ^. L. id ) (Right $ ApplyWorkspaceEditResult True Nothing Nothing )
314
- respond _ = pure ()
316
+ FromServerMess SMethod_WorkspaceConfiguration r -> do
317
+ let requestedSections = mapMaybe (\ i -> i ^? L. section . _Just) $ r ^. L. params . L. items
318
+ c <- curLspConfig <$> get @ SessionState
319
+ case c of
320
+ Object o -> do
321
+ let configsOrErrs = (flip fmap ) requestedSections $ \ section ->
322
+ case o ^. at (fromString $ T. unpack section) of
323
+ Just config -> Right config
324
+ Nothing -> Left section
325
+
326
+ let (errs, configs) = partitionEithers configsOrErrs
327
+
328
+ if null errs
329
+ then sendMessage $ TResponseMessage " 2.0" (Just $ r ^. L. id ) (Right configs)
330
+ else sendMessage @ _ @ (TResponseError Method_WorkspaceConfiguration ) $
331
+ TResponseError (InL LSPErrorCodes_RequestFailed ) (" No configuration for requested sections: " <> (T. pack $ show errs)) Nothing
332
+
333
+ _ -> sendMessage @ _ @ (TResponseError Method_WorkspaceConfiguration ) $ TResponseError (InL LSPErrorCodes_RequestFailed ) " No configuration" Nothing
334
+ _ -> pure ()
335
+ unless ((ignoreLogNotifications (config context) && isLogNotification msg) || (ignoreConfigurationRequests (config context) && isConfigRequest msg)) $
336
+ yield msg
337
+
338
+ where
339
+
340
+ isLogNotification (FromServerMess SMethod_WindowShowMessage _) = True
341
+ isLogNotification (FromServerMess SMethod_WindowLogMessage _) = True
342
+ isLogNotification (FromServerMess SMethod_WindowShowDocument _) = True
343
+ isLogNotification _ = False
315
344
345
+ isConfigRequest (FromServerMess SMethod_WorkspaceConfiguration _) = True
346
+ isConfigRequest _ = False
316
347
317
348
-- extract Uri out from DocumentChange
318
349
-- didn't put this in `lsp-types` because TH was getting in the way
0 commit comments